From dc3f7cc0f4a97c596141e59266b0c5bb7534ef51 Mon Sep 17 00:00:00 2001 From: laureng-hd Date: Sun, 21 Jan 2024 00:22:11 -0800 Subject: [PATCH] udates to sync paramter and externalId outputs --- .Rhistory | 5 ++ NAMESPACE | 2 + R/get_tests.R | 96 +++++++++++++++++++++++++++---- R/get_tests_ath.R | 108 +++++++++++++++++++++++++++++++---- R/get_tests_group.R | 125 +++++++++++++++++++++++++++++++++++----- R/get_tests_team.R | 126 ++++++++++++++++++++++++++++++++++++----- R/get_tests_type.R | 99 +++++++++++++++++++++++++++++--- man/get_tests_ath.Rd | 6 +- man/get_tests_group.Rd | 6 +- man/get_tests_team.Rd | 6 +- man/get_tests_type.Rd | 6 +- 11 files changed, 522 insertions(+), 63 deletions(-) diff --git a/.Rhistory b/.Rhistory index e171678..dbc890a 100644 --- a/.Rhistory +++ b/.Rhistory @@ -83,3 +83,8 @@ library(gh) gh::gh_token("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") usethis::use_pkgdown_github_pages() usethis::use_pkgdown_github_pages() +usethis::use_pkgdown_github_pages() +getwd() +pkgdown::build_site() +pkgdown::build_site() +pkgdown::build_site() diff --git a/NAMESPACE b/NAMESPACE index 2cff68a..bb26850 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -12,6 +12,8 @@ export(get_tests_ath) export(get_tests_group) export(get_tests_team) export(get_tests_type) +importFrom(dplyr,relocate) +importFrom(dplyr,select) importFrom(magrittr,"%>%") importFrom(rlang,.data) importFrom(tidyr,unnest) diff --git a/R/get_tests.R b/R/get_tests.R index 83e47dc..b2a1ba4 100644 --- a/R/get_tests.R +++ b/R/get_tests.R @@ -67,6 +67,8 @@ #' #' @importFrom rlang .data #' @importFrom tidyr unnest +#' @importFrom dplyr select +#' @importFrom dplyr relocate #' @export ## Get All Tests or Sync Tests ----- @@ -99,25 +101,23 @@ get_tests <- function(from = NULL, to = NULL, sync = FALSE) { # From DateTime fromDT <- if(base::is.null(from)) { "" - } else if(!is.numeric(from)) { - base::stop("date must be in numeric unix format") - } else{ - base::paste0("&from=",from) + } else if(base::is.numeric(from) && base::isTRUE(sync)) { + base::paste0("?syncFrom=",from) + } else if(base::is.numeric(from) && base::isFALSE(sync)) { + base::paste0("?from=",from) } # To DateTime toDT <- if(base::is.null(to)) { "" - } else if(!is.numeric(to)) { - base::stop("date must be in numeric unix format") - } else if(base::is.null(from)) { + } else if(base::is.null(from) && base::isFALSE(sync)) { base::paste0("?to=",to) } else if(base::is.null(from) && base::isTRUE(sync)) { base::paste0("?syncTo=",to) - } else if(base::isTRUE(sync)) { + } else if(base::is.numeric(to) && base::isTRUE(sync)) { base::paste0("&syncTo=",to) - } else { + } else if(base::is.numeric(to) && base::isFALSE(sync)){ base::paste0("&to=",to) } @@ -167,11 +167,85 @@ get_tests <- function(from = NULL, to = NULL, sync = FALSE) { # The code ran successfully, and 'result' contains the data frame } + #-----# + ### Create data frame ### + #-----# + # Clean Resp Headers base::names(x) <- base::sub("^data\\.", "", base::names(x)) - # UnNest testType and Athlete data - x <- x %>% tidyr::unnest(c(.data$testType, .data$athlete), names_sep = ".") + ##-- External IDs --## + + # Create externalId df + extDF <- x$athlete$external + + # Prepare externalId vector + external <- base::c() + + # Loop externalId columns + for (i in 1:base::nrow(extDF)) { + + extRow <- NA + + for (n in 1:base::ncol(extDF)) { + + # get externalId name + extN <- base::names(extDF)[n] + + # get ext id + extId <- extDF[i,n] + + # create new external id name:id string + newExt <- base::paste0(extN, ":", extId) + + # add new externalId string to row list if needed + extRow <- if( base::is.na(extId) ) { + # if extId NA, no change + extRow + } else { + # Add new string to extId Row + extRow <- if( base::is.na(extRow) ) { + base::paste0(newExt) + } else{ + base::paste0(extRow, ",", newExt) + } + } + + } + + external <- base::c(external, extRow) + } + + # Athlete df from original df + a <- x$athlete + + # Remove old external from athlete df + a <- dplyr::select(.data = a, -dplyr::starts_with('external')) + + # Bind external column to athlete df + a <- base::cbind(a, external) + + # append Athlete prefix + base::names(a) <- base::paste0('athlete_', base::names(a)) + + ##-- Test Types --## + + # Create testType df + t <- x$testType + + # append testType prefix + base::names(t) <- base::paste0('testType_', base::names(t)) + + ##-- finish data frame --## + + # select trial metadata metrics from DF + x1 <- dplyr::select(.data = x, base::c('id', 'timestamp', 'segment')) + + # select all metrics from DF + x2 <- dplyr::select(.data = x, -base::c('id', 'timestamp', 'segment', 'testType', 'athlete')) + + # create new complete DF + x <- base::cbind(x1, t, a, x2) # Clean colnames with janitor x <- janitor::clean_names(x) diff --git a/R/get_tests_ath.R b/R/get_tests_ath.R index 3c020a0..4c0eb76 100644 --- a/R/get_tests_ath.R +++ b/R/get_tests_ath.R @@ -4,7 +4,7 @@ #' Get only tests of the specified athlete for an account. #' #' @usage -#' get_tests_ath(athleteId, from, to) +#' get_tests_ath(athleteId, from, to, sync) #' #' @param athleteId Supply an athlete’s id to receive tests for a specific athlete #' @@ -16,6 +16,10 @@ #' supply this value you will receive every test from the beginning of time or the optionally #' supplied `from` parameter. This parameter is best suited for bulk exports of historical data. #' +#' @param sync The result set will include updated and newly created tests. This parameter is best +#' suited to keep your database in sync with the Hawkin database. If you do not supply this value +#' you will receive every test. +#' #' @return #' Response will be a data frame containing the trials from the specified team and within the time range (if specified). #' @@ -64,10 +68,12 @@ #' #' @importFrom rlang .data #' @importFrom tidyr unnest +#' @importFrom dplyr select +#' @importFrom dplyr relocate #' @export ## Get Tests Data by Athlete Id ----- -get_tests_ath <- function(athleteId, from = NULL, to = NULL) { +get_tests_ath <- function(athleteId, from = NULL, to = NULL, sync = FALSE) { # Retrieve Access Token and Expiration from Environment Variables aToken <- base::Sys.getenv("accessToken") @@ -98,7 +104,9 @@ get_tests_ath <- function(athleteId, from = NULL, to = NULL) { "" } else if(!is.numeric(from)) { base::stop("date must be in numeric unix format") - } else{ + } else if(base::is.numeric(from) && base::isTRUE(sync)) { + base::paste0("&syncFrom=",from) + } else if(base::is.numeric(from) && base::isFALSE(sync)) { base::paste0("&from=",from) } @@ -107,10 +115,13 @@ get_tests_ath <- function(athleteId, from = NULL, to = NULL) { "" } else if(!is.numeric(to)) { base::stop("date must be in numeric unix format") - } else{ + } else if(base::is.numeric(to) && base::isTRUE(sync)) { + base::paste0("&syncTo=",to) + } else if(base::is.numeric(to) && base::isFALSE(sync)){ base::paste0("&to=",to) } + # Athlete Id aId <- if(base::is.character(athleteId)) { athleteId @@ -153,18 +164,92 @@ get_tests_ath <- function(athleteId, from = NULL, to = NULL) { # Evaluate Response x <- if(resp$count[1] > 0) { # Convert to data frame - df <- base::data.frame(resp) + x <- base::data.frame(resp) + + #-----# + ### Create data frame ### + #-----# # Clean Resp Headers - base::names(df) <- base::sub("^data\\.", "", base::names(df)) + base::names(x) <- base::sub("^data\\.", "", base::names(x)) + + ##-- External IDs --## + + # Create externalId df + extDF <- x$athlete$external + + # Prepare externalId vector + external <- base::c() + + # Loop externalId columns + for (i in 1:base::nrow(extDF)) { + + extRow <- NA + + for (n in 1:base::ncol(extDF)) { + + # get externalId name + extN <- base::names(extDF)[n] + + # get ext id + extId <- extDF[i,n] + + # create new external id name:id string + newExt <- base::paste0(extN, ":", extId) + + # add new externalId string to row list if needed + extRow <- if( base::is.na(extId) ) { + # if extId NA, no change + extRow + } else { + # Add new string to extId Row + extRow <- if( base::is.na(extRow) ) { + base::paste0(newExt) + } else{ + base::paste0(extRow, ",", newExt) + } + } - # UnNest testType and Athlete data - df <- df %>% tidyr::unnest(c(.data$testType, .data$athlete), names_sep = ".") + } - # Clean column names with janitor - df <- janitor::clean_names(df) + external <- base::c(external, extRow) + } - df + # Athlete df from original df + a <- x$athlete + + # Remove old external from athlete df + a <- dplyr::select(.data = a, -dplyr::starts_with('external')) + + # Bind external column to athlete df + a <- base::cbind(a, external) + + # append Athlete prefix + base::names(a) <- base::paste0('athlete_', base::names(a)) + + ##-- Test Types --## + + # Create testType df + t <- x$testType + + # append testType prefix + base::names(t) <- base::paste0('testType_', base::names(t)) + + ##-- finish data frame --## + + # select trial metadata metrics from DF + x1 <- dplyr::select(.data = x, base::c('id', 'timestamp', 'segment')) + + # select all metrics from DF + x2 <- dplyr::select(.data = x, -base::c('id', 'timestamp', 'segment', 'testType', 'athlete')) + + # create new complete DF + x <- base::cbind(x1, t, a, x2) + + # Clean colnames with janitor + x <- janitor::clean_names(x) + + x } else { base::stop("No trials returned. Check athleteId or from/to entries") } @@ -177,4 +262,3 @@ get_tests_ath <- function(athleteId, from = NULL, to = NULL) { return(Resp) } - diff --git a/R/get_tests_group.R b/R/get_tests_group.R index f26b36e..e7cc913 100644 --- a/R/get_tests_group.R +++ b/R/get_tests_group.R @@ -4,7 +4,7 @@ #' Get only tests of the specified group for an account. #' #' @usage -#' get_tests_group(groupId, from, to) +#' get_tests_group(groupId, from, to, sync) #' #' @param groupId Supply a group’s or a string of a comma separated list of group id’s to receive tests from #' specific groups. Recommended to use method `paste0()`. A maximum of 10 groups can be fetched at once. @@ -17,6 +17,10 @@ #' supply this value you will receive every test from the beginning of time or the optionally #' supplied `from` parameter. This parameter is best suited for bulk exports of historical data. #' +#' @param sync The result set will include updated and newly created tests. This parameter is best +#' suited to keep your database in sync with the Hawkin database. If you do not supply this value +#' you will receive every test. +#' #' @return #' Response will be a data frame containing the trials from the specified team and within the time #' range (if specified). @@ -66,10 +70,12 @@ #' #' @importFrom rlang .data #' @importFrom tidyr unnest +#' @importFrom dplyr select +#' @importFrom dplyr relocate #' @export ## Get Tests Data by Group Id ----- -get_tests_group <- function(groupId, from = NULL, to = NULL) { +get_tests_group <- function(groupId, from = NULL, to = NULL, sync = FALSE) { # Retrieve Access Token and Expiration from Environment Variables aToken <- base::Sys.getenv("accessToken") @@ -98,17 +104,26 @@ get_tests_group <- function(groupId, from = NULL, to = NULL) { # From DateTime fromDT <- if(base::is.null(from)) { "" - } else { + } else if(!is.numeric(from)) { + base::stop("date must be in numeric unix format") + } else if(base::is.numeric(from) && base::isTRUE(sync)) { + base::paste0("&syncFrom=",from) + } else if(base::is.numeric(from) && base::isFALSE(sync)) { base::paste0("&from=",from) } # To DateTime toDT <- if(base::is.null(to)) { "" - } else { + } else if(!is.numeric(to)) { + base::stop("date must be in numeric unix format") + } else if(base::is.numeric(to) && base::isTRUE(sync)) { + base::paste0("&syncTo=",to) + } else if(base::is.numeric(to) && base::isFALSE(sync)){ base::paste0("&to=",to) } + # Group Id gId <- if(base::is.character(groupId)) { groupId @@ -162,26 +177,110 @@ get_tests_group <- function(groupId, from = NULL, to = NULL) { # The code ran successfully, and 'result' contains the data frame } + #-----# + ### Create data frame ### + #-----# + + ##--- Filter cases ---### + # Clean Resp Headers base::names(x) <- base::sub("^data\\.", "", base::names(x)) - # UnNest testType and Athlete data - x <- x %>% tidyr::unnest(c(.data$testType, .data$athlete), names_sep = ".") - # Split the ID string into individual IDs groupIds <- base::unlist(base::strsplit(groupId, ",")) # Check if any of the IDs in groupIds are present in any of the lists in the 'athlete.teams' column filtered_df <- x %>% - dplyr::filter(base::any(base::sapply(.data$athlete.groups, function(ids) base::any(ids %in% groupIds)))) - - # Clean column names with janitor - filtered_df <- janitor::clean_names(filtered_df) + dplyr::filter(base::any(base::sapply(.data$athlete$groups, function(ids) base::any(ids %in% groupIds)))) + ### # Use an if statement to handle the cases x <- if (base::nrow(filtered_df) > 0) { # Data matching the ID(s) was found - filtered_df + x <- filtered_df + + #-----# + ### Create data frame ### + #-----# + + ##-- External IDs --## + + # Create externalId df + extDF <- x$athlete$external + + # Prepare externalId vector + external <- base::c() + + # Loop externalId columns + for (i in 1:base::nrow(extDF)) { + + extRow <- NA + + for (n in 1:base::ncol(extDF)) { + + # get externalId name + extN <- base::names(extDF)[n] + + # get ext id + extId <- extDF[i,n] + + # create new external id name:id string + newExt <- base::paste0(extN, ":", extId) + + # add new externalId string to row list if needed + extRow <- if( base::is.na(extId) ) { + # if extId NA, no change + extRow + } else { + # Add new string to extId Row + extRow <- if( base::is.na(extRow) ) { + base::paste0(newExt) + } else{ + base::paste0(extRow, ",", newExt) + } + } + + } + + external <- base::c(external, extRow) + } + + # Athlete df from original df + a <- x$athlete + + # Remove old external from athlete df + a <- dplyr::select(.data = a, -dplyr::starts_with('external')) + + # Bind external column to athlete df + a <- base::cbind(a, external) + + # append Athlete prefix + base::names(a) <- base::paste0('athlete_', base::names(a)) + + ##-- Test Types --## + + # Create testType df + t <- x$testType + + # append testType prefix + base::names(t) <- base::paste0('testType_', base::names(t)) + + ##-- finish data frame --## + + # select trial metadata metrics from DF + x1 <- dplyr::select(.data = x, base::c('id', 'timestamp', 'segment')) + + # select all metrics from DF + x2 <- dplyr::select(.data = x, -base::c('id', 'timestamp', 'segment', 'testType', 'athlete')) + + # create new complete DF + x <- base::cbind(x1, t, a, x2) + + # Clean colnames with janitor + x <- janitor::clean_names(x) + + x + } else { base::stop("No data returned. Check groupId") } @@ -191,9 +290,7 @@ get_tests_group <- function(groupId, from = NULL, to = NULL) { #-----# - # Return Response return(Resp) } - diff --git a/R/get_tests_team.R b/R/get_tests_team.R index dba349c..ef1d329 100644 --- a/R/get_tests_team.R +++ b/R/get_tests_team.R @@ -4,7 +4,7 @@ #' Get only tests of the specified team for an account. #' #' @usage -#' get_tests_team(teamId, from, to) +#' get_tests_team(teamId, from, to, sync) #' #' @param teamId Supply a team’s or a string of a comma separated list of group id’s to receive tests from #' specific groups. Recommended to use method `paste0()`. A maximum of 10 groups can be fetched at once. @@ -17,6 +17,10 @@ #' supply this value you will receive every test from the beginning of time or the optionally #' supplied `from` parameter. This parameter is best suited for bulk exports of historical data. #' +#' @param sync The result set will include updated and newly created tests. This parameter is best +#' suited to keep your database in sync with the Hawkin database. If you do not supply this value +#' you will receive every test. +#' #' @return #' Response will be a data frame containing the trials from the specified team and within the time range (if specified). #' @@ -65,10 +69,12 @@ #' #' @importFrom rlang .data #' @importFrom tidyr unnest +#' @importFrom dplyr select +#' @importFrom dplyr relocate #' @export ## Get Tests Data by Team Id ----- -get_tests_team <- function(teamId, from = NULL, to = NULL) { +get_tests_team <- function(teamId, from = NULL, to = NULL, sync = FALSE) { # Retrieve Access Token and Expiration from Environment Variables aToken <- base::Sys.getenv("accessToken") @@ -97,14 +103,22 @@ get_tests_team <- function(teamId, from = NULL, to = NULL) { # From DateTime fromDT <- if(base::is.null(from)) { "" - } else { + } else if(!is.numeric(from)) { + base::stop("date must be in numeric unix format") + } else if(base::is.numeric(from) && base::isTRUE(sync)) { + base::paste0("&syncFrom=",from) + } else if(base::is.numeric(from) && base::isFALSE(sync)) { base::paste0("&from=",from) } # To DateTime toDT <- if(base::is.null(to)) { "" - } else { + } else if(!is.numeric(to)) { + base::stop("date must be in numeric unix format") + } else if(base::is.numeric(to) && base::isTRUE(sync)) { + base::paste0("&syncTo=",to) + } else if(base::is.numeric(to) && base::isFALSE(sync)){ base::paste0("&to=",to) } @@ -161,28 +175,113 @@ get_tests_team <- function(teamId, from = NULL, to = NULL) { # The code ran successfully, and 'result' contains the data frame } + #-----# + ### Create data frame ### + #-----# + + ##--- Filter cases ---### + # Clean Resp Headers base::names(x) <- base::sub("^data\\.", "", base::names(x)) - # UnNest testType and Athlete data - x <- x %>% tidyr::unnest(c(.data$testType, .data$athlete), names_sep = ".") - # Split the ID string into individual IDs teamIds <- base::unlist(base::strsplit(teamId, ",")) - # Check if any of the IDs in teamIds are present in any of the lists in the 'athlete.teams' column + # Check if any of the IDs in teamIds are present in any of the lists in the 'teams' column filtered_df <- x %>% - dplyr::filter(base::any(base::sapply(.data$athlete.teams, function(ids) base::any(ids %in% teamIds)))) + dplyr::filter(base::any(base::sapply(.data$athlete$teams, function(ids) base::any(ids %in% teamIds)))) - # Clean column names with janitor - filtered_df <- janitor::clean_names(filtered_df) + ### # Use an if statement to handle the cases x <- if (base::nrow(filtered_df) > 0) { # Data matching the ID(s) was found - filtered_df + x <- filtered_df + + #-----# + ### Create data frame ### + #-----# + + ##-- External IDs --## + + # Create externalId df + extDF <- x$athlete$external + + # Prepare externalId vector + external <- base::c() + + # Loop externalId columns + for (i in 1:base::nrow(extDF)) { + + extRow <- NA + + for (n in 1:base::ncol(extDF)) { + + # get externalId name + extN <- base::names(extDF)[n] + + # get ext id + extId <- extDF[i,n] + + # create new external id name:id string + newExt <- base::paste0(extN, ":", extId) + + # add new externalId string to row list if needed + extRow <- if( base::is.na(extId) ) { + # if extId NA, no change + extRow + } else { + # Add new string to extId Row + extRow <- if( base::is.na(extRow) ) { + base::paste0(newExt) + } else{ + base::paste0(extRow, ",", newExt) + } + } + + } + + external <- base::c(external, extRow) + } + + # Athlete df from original df + a <- x$athlete + + # Remove old external from athlete df + a <- dplyr::select(.data = a, -dplyr::starts_with('external')) + + # Bind external column to athlete df + a <- base::cbind(a, external) + + # append Athlete prefix + base::names(a) <- base::paste0('athlete_', base::names(a)) + + ##-- Test Types --## + + # Create testType df + t <- x$testType + + # append testType prefix + base::names(t) <- base::paste0('testType_', base::names(t)) + + ##-- finish data frame --## + + # select trial metadata metrics from DF + x1 <- dplyr::select(.data = x, base::c('id', 'timestamp', 'segment')) + + # select all metrics from DF + x2 <- dplyr::select(.data = x, -base::c('id', 'timestamp', 'segment', 'testType', 'athlete')) + + # create new complete DF + x <- base::cbind(x1, t, a, x2) + + # Clean colnames with janitor + x <- janitor::clean_names(x) + + x + } else { - base::stop("No data returned. Check teamId") + base::stop("No data returned. Check groupId") } x @@ -190,7 +289,6 @@ get_tests_team <- function(teamId, from = NULL, to = NULL) { #-----# - # Return Response return(Resp) diff --git a/R/get_tests_type.R b/R/get_tests_type.R index 6189f47..187624a 100644 --- a/R/get_tests_type.R +++ b/R/get_tests_type.R @@ -4,7 +4,7 @@ #' Get only tests of the specified type for an account. #' #' @usage -#' get_tests_type(typeId, from, to) +#' get_tests_type(typeId, from, to, sync) #' #' @param typeId Supply a test type id to only retrieve tests of that type. #' @@ -16,6 +16,10 @@ #' supply this value you will receive every test from the beginning of time or the optionally #' supplied `from` parameter. This parameter is best suited for bulk exports of historical data. #' +#' @param sync The result set will include updated and newly created tests. This parameter is best +#' suited to keep your database in sync with the Hawkin database. If you do not supply this value +#' you will receive every test. +#' #' @return #' Response will be a data frame containing the trials of the specified type and within the time range (if specified). #' @@ -63,11 +67,13 @@ #' #' @importFrom rlang .data #' @importFrom tidyr unnest +#' @importFrom dplyr select +#' @importFrom dplyr relocate #' @export ## Get Tests Data by Test Type ----- -get_tests_type <- function(typeId, from = NULL, to = NULL) { +get_tests_type <- function(typeId, from = NULL, to = NULL, sync = FALSE) { # Retrieve Access Token and Expiration from Environment Variables aToken <- base::Sys.getenv("accessToken") @@ -98,7 +104,9 @@ get_tests_type <- function(typeId, from = NULL, to = NULL) { "" } else if(!is.numeric(from)) { base::stop("date must be in numeric unix format") - } else{ + } else if(base::is.numeric(from) && base::isTRUE(sync)) { + base::paste0("&syncFrom=",from) + } else if(base::is.numeric(from) && base::isFALSE(sync)) { base::paste0("&from=",from) } @@ -107,7 +115,9 @@ get_tests_type <- function(typeId, from = NULL, to = NULL) { "" } else if(!is.numeric(to)) { base::stop("date must be in numeric unix format") - } else{ + } else if(base::is.numeric(to) && base::isTRUE(sync)) { + base::paste0("&syncTo=",to) + } else if(base::is.numeric(to) && base::isFALSE(sync)){ base::paste0("&to=",to) } @@ -176,13 +186,87 @@ get_tests_type <- function(typeId, from = NULL, to = NULL) { # The code ran successfully, and 'result' contains the data frame } + #-----# + ### Create data frame ### + #-----# + # Clean Resp Headers base::names(x) <- base::sub("^data\\.", "", base::names(x)) - # UnNest testType and Athlete data - x <- x %>% tidyr::unnest(c(.data$testType, .data$athlete), names_sep = ".") + ##-- External IDs --## + + # Create externalId df + extDF <- x$athlete$external + + # Prepare externalId vector + external <- base::c() + + # Loop externalId columns + for (i in 1:base::nrow(extDF)) { + + extRow <- NA + + for (n in 1:base::ncol(extDF)) { + + # get externalId name + extN <- base::names(extDF)[n] + + # get ext id + extId <- extDF[i,n] + + # create new external id name:id string + newExt <- base::paste0(extN, ":", extId) + + # add new externalId string to row list if needed + extRow <- if( base::is.na(extId) ) { + # if extId NA, no change + extRow + } else { + # Add new string to extId Row + extRow <- if( base::is.na(extRow) ) { + base::paste0(newExt) + } else{ + base::paste0(extRow, ",", newExt) + } + } + + } + + external <- base::c(external, extRow) + } + + # Athlete df from original df + a <- x$athlete + + # Remove old external from athlete df + a <- dplyr::select(.data = a, -dplyr::starts_with('external')) + + # Bind external column to athlete df + a <- base::cbind(a, external) + + # append Athlete prefix + base::names(a) <- base::paste0('athlete_', base::names(a)) + + ##-- Test Types --## + + # Create testType df + t <- x$testType - # Clean column names with janitor + # append testType prefix + base::names(t) <- base::paste0('testType_', base::names(t)) + + ##-- finish data frame --## + + # select trial metadata metrics from DF + x1 <- dplyr::select(.data = x, base::c('id', 'timestamp', 'segment')) + + # select all metrics from DF + x2 <- dplyr::select(.data = x, -base::c('id', 'timestamp', 'segment', 'testType', 'athlete')) + + # create new complete DF + x <- base::cbind(x1, t, a, x2) + + # Clean colnames with janitor x <- janitor::clean_names(x) x @@ -190,7 +274,6 @@ get_tests_type <- function(typeId, from = NULL, to = NULL) { #-----# - # Return Response return(Resp) diff --git a/man/get_tests_ath.Rd b/man/get_tests_ath.Rd index 03a9b21..27d838b 100644 --- a/man/get_tests_ath.Rd +++ b/man/get_tests_ath.Rd @@ -4,7 +4,7 @@ \alias{get_tests_ath} \title{Get Test Trials By Athlete} \usage{ -get_tests_ath(athleteId, from, to) +get_tests_ath(athleteId, from, to, sync) } \arguments{ \item{athleteId}{Supply an athlete’s id to receive tests for a specific athlete} @@ -16,6 +16,10 @@ historical data} \item{to}{Optionally supply a time (Unix timestamp) you want the tests to. If you do not supply this value you will receive every test from the beginning of time or the optionally supplied \code{from} parameter. This parameter is best suited for bulk exports of historical data.} + +\item{sync}{The result set will include updated and newly created tests. This parameter is best +suited to keep your database in sync with the Hawkin database. If you do not supply this value +you will receive every test.} } \value{ Response will be a data frame containing the trials from the specified team and within the time range (if specified). diff --git a/man/get_tests_group.Rd b/man/get_tests_group.Rd index aaccc4a..9c9d196 100644 --- a/man/get_tests_group.Rd +++ b/man/get_tests_group.Rd @@ -4,7 +4,7 @@ \alias{get_tests_group} \title{Get Test Trials By Groups} \usage{ -get_tests_group(groupId, from, to) +get_tests_group(groupId, from, to, sync) } \arguments{ \item{groupId}{Supply a group’s or a string of a comma separated list of group id’s to receive tests from @@ -17,6 +17,10 @@ historical data.} \item{to}{Optionally supply a time (Unix timestamp) you want the tests to. If you do not supply this value you will receive every test from the beginning of time or the optionally supplied \code{from} parameter. This parameter is best suited for bulk exports of historical data.} + +\item{sync}{The result set will include updated and newly created tests. This parameter is best +suited to keep your database in sync with the Hawkin database. If you do not supply this value +you will receive every test.} } \value{ Response will be a data frame containing the trials from the specified team and within the time diff --git a/man/get_tests_team.Rd b/man/get_tests_team.Rd index ad4d18c..0f33798 100644 --- a/man/get_tests_team.Rd +++ b/man/get_tests_team.Rd @@ -4,7 +4,7 @@ \alias{get_tests_team} \title{Get Test Trials By Teams} \usage{ -get_tests_team(teamId, from, to) +get_tests_team(teamId, from, to, sync) } \arguments{ \item{teamId}{Supply a team’s or a string of a comma separated list of group id’s to receive tests from @@ -17,6 +17,10 @@ historical data.} \item{to}{Optionally supply a time (Unix timestamp) you want the tests to. If you do not supply this value you will receive every test from the beginning of time or the optionally supplied \code{from} parameter. This parameter is best suited for bulk exports of historical data.} + +\item{sync}{The result set will include updated and newly created tests. This parameter is best +suited to keep your database in sync with the Hawkin database. If you do not supply this value +you will receive every test.} } \value{ Response will be a data frame containing the trials from the specified team and within the time range (if specified). diff --git a/man/get_tests_type.Rd b/man/get_tests_type.Rd index 40d5d76..1f6ab4b 100644 --- a/man/get_tests_type.Rd +++ b/man/get_tests_type.Rd @@ -4,7 +4,7 @@ \alias{get_tests_type} \title{Get Test Trials By Test Type} \usage{ -get_tests_type(typeId, from, to) +get_tests_type(typeId, from, to, sync) } \arguments{ \item{typeId}{Supply a test type id to only retrieve tests of that type.} @@ -16,6 +16,10 @@ historical data.} \item{to}{Optionally supply a time (Unix timestamp) you want the tests to. If you do not supply this value you will receive every test from the beginning of time or the optionally supplied \code{from} parameter. This parameter is best suited for bulk exports of historical data.} + +\item{sync}{The result set will include updated and newly created tests. This parameter is best +suited to keep your database in sync with the Hawkin database. If you do not supply this value +you will receive every test.} } \value{ Response will be a data frame containing the trials of the specified type and within the time range (if specified).