R/Utilities.R

Defines functions generateAPIfunctions generatePkgdownYmlFile deleteDataObject createDataObject modifyDataObject getDataObject getAllDataObjectsForObject createSearchSort getAllSearchConditionTypes getFieldsForObject getObjectsForModuleAndEntity getModulesForEntity getAllEntities getAllDistricts makeRequest flattenJsonList characterizeDataFrame addSearchFields checkSkywardAuthentication

Documented in getAllDistricts getAllEntities getAllSearchConditionTypes

### This function checks for authentication-related options which must be set using the "options" function.
checkSkywardAuthentication <- function(){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  # Try sourcing local credentials file.
  tryCatch({
    
    source('SkywardCredentials.R')
    
  }, error = function(e) {invisible()}
  
  )
   
  requiredOptions <- c("consumerKey", "consumerSecret", "apiUrl")
  
  for(option in requiredOptions){
    if(Sys.getenv(option) == ''){
      stop(paste0('Required option ', option, ' has not been set! Set its value using Sys.setenv(', option, ' = "{', option, 'Value}").'))
    }
  }
}

# This function properly formats search field parameters for inclusion in a Skyward Generic API request.
addSearchFields <- function(endpoint, params){
  
  params = params[as.character(params) != 'NULL']
  
  params <- sort(params)
  paramsString <- paste0('?searchFields=', paste(params, collapse = '&searchFields='))
  
  return(paste0(endpoint, paramsString))
}

# This function converts a dataframe of varying classes to all character.
characterizeDataFrame <- function(df){
  
  # Remove empty columns
  df = df[!(as.logical(lapply(df, length) == 0))]
  df = data.frame(df, stringsAsFactors = FALSE)
  
  # Convert columns to character vectors
  for(i in 1:length(names(df))){
    
    df[,i] = as.character(df[,i])
  }
  
  return(data.frame(df, stringsAsFactors = FALSE))
}

# This function consistently flattens a json list into a dataframe.
flattenJsonList <- function(jsonList){
  
  for(item in jsonList){
    
    item = data.frame(item, stringsAsFactors = F)
    
    if(!exists('df', inherits = FALSE)){
      df <- jsonlite::flatten(item)
    }else{
      df <- bind_rows(df, jsonlite::flatten(item))
    }
  }
  return(df)
}

#' Perform API Request to Endpoint
#' 
#' This function performs an HTTP request to a Skyward API endpoint.
#' 
#' This function is called by all Skyward SDK functions.
#' You will, in general, not need to call this function directly.
#' @param endpoint The endpoint URL for the request.
#' @param searchFields A list of parameters primarily used as searchFields.
#' @param verb An HTTP request, either GET, PUT, POST or DELETE.
#' @param payload A json object used in PUT and POST requests. \cr Use jsonlite::fromJSON(jsonlite::toJSON(\{yourNamedList\}, pretty = T)).
#' @concept Requests
#' @return The content of the request response.
#' @section References:
#' \{yourApiUrl\}/swagger\cr\cr
#' \href{https://help.skyward.com/}{Skyward's Knowledge Hub}
#' @export
makeRequest <- function(endpoint, searchFields = NULL, verb = 'GET', payload = NULL){
  
  suppressWarnings(suppressMessages({
    
  checkSkywardAuthentication()
    
  }))
  
  Sys.sleep(.1)  
  
  # See https://github.com/r-lib/httr/blob/master/demo/oauth1-nounproject.r for Oauth1.0 1-leg fix.
  skyward_app <- httr::oauth_app("Skyward",
                                 key = Sys.getenv('consumerKey'),
                                 secret = Sys.getenv('consumerSecret'))
  
  # Remove ending / if it's present.
  endpoint <- gsub('//', '/', ifelse(regexpr('./$', endpoint) > 0, substr(endpoint, 1, nchar(endpoint)-1), endpoint))
  if(!is.null(searchFields)) {
    endpoint <- addSearchFields(endpoint, searchFields)
  }
  
  # Make absolutely sure only one / between apiUrl and endpoint.
  apiUrl <- Sys.getenv('apiUrl')
  apiUrl <- ifelse(regexpr('./$', apiUrl) > 0, apiUrl, paste0(apiUrl, '/'))
  endpoint <- ifelse(substr(endpoint, 1, 1) == '/', substr(endpoint, 2, nchar(endpoint)), endpoint)
  
  url <- paste0(apiUrl, endpoint)
  
  sig <- httr::oauth_signature(url, method = verb, app = skyward_app)
  header_oauth <- httr::oauth_header(sig)
  
  eval(parse(text = paste0('response <- httr::', verb, '(url, header_oauth, body = payload, encode = "json", httr::accept_json())')))
  
  if(response$status_code < 300){
    return(httr::content(response))
  }else{
    
    responseContent <- httr::content(response)
    seeLogMessage <- 'See Log #'
    
    # If instead of an error message the server returns reference to a log...
    if(responseContent %>% stringr::str_detect(seeLogMessage)){
      
      logNumber <- responseContent %>% stringr::str_sub((responseContent %>% stringr::str_locate(seeLogMessage))[[2]] + 1, (responseContent %>% stringr::str_locate(' for details'))[[1]] - 1)
      
      stop(paste0(makeRequest(paste0('Generic/1/SkySys/Log/', logNumber), searchFields = 'Message')$Message, '. See Log #', logNumber, ' for details. ', paste0(Sys.getenv('apiUrl') %>% stringr::str_replace('API', ''), '/SkySys/Log/Details/', logNumber)))
    }
    
    stop(httr::content(response))
  }
}

# See Swagger documentation for API at {apiURL}/swagger/ui/index#/Generic

#' Get all Districts
#'
#' This function returns the ids and names of all districts associated with a system.
#'
#' @concept General
#' @return All ids and names for all districts.
#' @section References:
#' \{yourApiUrl\}/swagger\cr\cr
#' \href{https://help.skyward.com/}{Skyward's Knowledge Hub}
#' @export
getAllDistricts <- function(){
  
  json <- makeRequest('Generic/GetSystemMetadata')
  json <- jsonlite::fromJSON(jsonlite::toJSON(json), simplifyDataFrame = T)
  
  districts <- json$System$Districts
  districts <- districts[which(names(districts) != 'Entities')] %>% jsonlite::flatten(recursive = F) %>% lapply(unlist) %>% as.data.frame(stringsAsFactors = F)
  
  return(districts)
}

# See Swagger documentation for API at {apiURL}/swagger/ui/index#/Generic

#' Get all Entities in District
#'
#' This function returns the ids and names of all entities associated with a district.
#'
#' @concept General
#' @return All ids and names for all district entities.
#' @section References:
#' \{yourApiUrl\}/swagger\cr\cr
#' \href{https://help.skyward.com/}{Skyward's Knowledge Hub}
#' @export
getAllEntities <- function(){
  
  systemMetadata <- makeRequest('Generic/GetSystemMetadata')
  districts <- systemMetadata$System$Districts

  for(district in districts){
    
      entities <- district$Entities
      district$Entities <- NULL
      
      entities <- (jsonlite::fromJSON(jsonlite::toJSON(list(district)), flatten = T) %>% jsonlite::flatten(recursive = F) %>% lapply(unlist) %>% as.data.frame(stringsAsFactors = F)) %>% dplyr::bind_rows(jsonlite::fromJSON(jsonlite::toJSON(entities), flatten = T) %>% jsonlite::flatten(recursive = F) %>% lapply(unlist) %>% as.data.frame(stringsAsFactors = F) %>% dplyr::select(-DistrictID)) %>% dplyr::select(EntityID, Name, Code, href, starts_with('SchoolYear'), DistrictID) %>% dplyr::mutate(IsDistrict = ifelse(DistrictID == 'NULL', F, T)) %>% dplyr::select(-DistrictID) %>% dplyr::mutate(InDistrict = district$DistrictID)
    }
  
  return(entities)
}

############ NOT MODIFIED
getModulesForEntity <- function(EntityID = 1){
  
  Modules <- names(makeRequest(paste('Generic', EntityID, sep = '/')))
  
  return(Modules)
}

######### MODIFIED ... added scopes to returned object and removed "Names" from function name.
getObjectsForModuleAndEntity <- function(Module, EntityID = 1){
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  Objects <- makeRequest(ModuleEndpoint)
  
  Objects <- data.frame(ObjectName = names(Objects), Scope = as.character(unlist(lapply(Objects, function(x) x$Scope))), stringsAsFactors = F)
  
  return(Objects)
}

######## MODIFIED... added DisplayName, Nullable and DataType fields.
getFieldsForObject <- function(Module, ObjectName, EntityID = 1){
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  Object <- makeRequest(ObjectEndpoint)
  Object$Relationships <- NULL
  Object$APIOptionFlags <- NULL
  
  displayName <- unlist(lapply(Object, function(x) x$DisplayName))
  primaryKey <- unlist(lapply(Object, function(x) ifelse(exists('PrimaryKey', x), T, F)))
  readOnly <- unlist(lapply(Object, function(x) ifelse(exists('ReadOnly', x), T, F)))
  nullable <- unlist(lapply(Object, function(x) ifelse(exists('Nullable', x), T, F)))
  dataType <- unlist(lapply(Object, function(x) x$DataType))
  
  Fields <- data.frame(Field = names(Object), DisplayName = displayName, ReadOnly = readOnly, PrimaryKey = primaryKey, Nullable = nullable, row.names = NULL, stringsAsFactors = F)
  
  return(Fields)
}

# See Swagger documentation for API at {apiURL}/swagger/ui/index#/Generic

#' Get all Search Conditions Types for use in Filtering
#'
#' This function returns the Search Conditions that can be used to filter API GET requests.
#'
#' @concept General
#' @return All search condition types for filtering.
#' @section References:
#' \{yourApiUrl\}/swagger\cr\cr
#' \href{https://help.skyward.com/}{Skyward's Knowledge Hub}
#' @export
getAllSearchConditionTypes <- function(){
  
  ConditionTypes <- c('Less', 'LessEqual', 'Equal', 'NotEqual', 'GreaterEqual', 'Greater', 'BetweenInclusive', 'BetweenExclusive', 'Null', 'NotNull', 'List', 'NotList', 'Like', 'NotLike', 'Begins', 'NotBegins', 'Contains', 'NotContains', 'Ends', 'NotEnds')
  
  return(ConditionTypes)
}

createSearchSort <- function(FieldNamesList, SortDecendingList = rep(F, length(FieldNamesList))){
  
  return(data.frame(FieldName = FieldNamesList, Descending = SortDecendingList, stringsAsFactors = F))
}

###### MODIFIED added the ability to use search criteria and sort results.
getAllDataObjectsForObject <- function(Module, ObjectName, DataObjectFields = 'all', EntityID = 1, SearchConditionsList = NULL, SearchConditionsGroupType = 'And', SearchSortFieldNamesList = NULL, SearchSortFieldNamesDescendingList = rep(F, length(SearchSortFieldNamesList)), Page = 1, PageSize = '100000'){
 
  suppressMessages(suppressWarnings(require(dplyr)))
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  if('all' %in% DataObjectFields){
    DataObjectFields <- getFieldsForObject(Module, ObjectName, EntityID)$Field
  }
  
  SearchObject <- NULL
  if(!all(is.null(SearchConditionsList), is.null(SearchSortFieldNamesList))){
    
   SearchObjectText <- 'jsonlite::fromJSON(jsonlite::toJSON(list(' ## -----
   
    # If search conditions were specified...
    if(!is.null(SearchConditionsList)){
      
      if(length(SearchConditionsGroupType) > 1 | !SearchConditionsGroupType %in% c('Or', 'And')) stop("Please select a single, valid SearchConditionsGroupType 'Or' or 'And'")
      
      allConditionTypes <- getAllSearchConditionTypes()
      
      SearchConditionsListConditionTypes <- unlist(lapply(SearchConditionsList, function(x) allConditionTypes[unlist(lapply(allConditionTypes, function(ConditionType) x %>% stringr::str_detect(paste0(' ', ConditionType, ' '))))]))
      
      SearchObjectText <- paste0(SearchObjectText, 'SearchCondition = list(SearchConditionGroup = list(ConditionGroupType = "', SearchConditionsGroupType, '", conditions = list(') ### --
      
      for(i in 1:length(SearchConditionsList)){
        
        ConditionType <- SearchConditionsListConditionTypes[[i]]
        FieldName <- SearchConditionsList[[i]] %>% stringr::str_sub(1, (SearchConditionsList[[i]] %>% stringr::str_locate(pattern = ConditionType))[[1]] - 2)
        Value <- SearchConditionsList[[i]] %>% stringr::str_replace(paste(FieldName, ConditionType, ''), '') %>% stringr::str_replace_all('"', '') %>% stringr::str_replace_all("'", "")
        
        SearchObjectText <- paste0(SearchObjectText, 'list(StringSearchCondition = list(FieldName = "', FieldName, '", ConditionType = "', ConditionType, '", Value = "', Value, '"))', ifelse(i < length(SearchConditionsList), ', ','')) # BALANCED!
      }
      
      SearchObjectText <- paste0(SearchObjectText, ")))") ### -----
    }
     
    # If search sorts were specified...
    if(!is.null(SearchSortFieldNamesList)){
      
      # Add comma if SearchConditionsList exists also.
      if(!is.null(SearchConditionsList)) SearchObjectText <- paste0(SearchObjectText, ', ')
      
      SearchObjectText <- paste0(SearchObjectText, 'SearchSort = list(') #-
      
      for(i in 1:length(SearchSortFieldNamesList)){
        
        SearchObjectText <- paste0(SearchObjectText, 'list(FieldName = "', SearchSortFieldNamesList[[i]], '", Descending = ', SearchSortFieldNamesDescendingList[[i]], ')', ifelse(i < length(SearchSortFieldNamesList), ', ','')) # BALANCED!
        
      }
      
      SearchObjectText <- paste0(SearchObjectText, ")") #-
    }
    
    SearchObjectText <- paste0(SearchObjectText, "), pretty = T))") ### -----
   
    SearchObject <- eval(parse(text = SearchObjectText))
  }
  
  DataObjectEndpoint <- paste(ObjectEndpoint, paste0(Page, '/', PageSize), sep = '/')
  
  DataObjects <- makeRequest(endpoint = DataObjectEndpoint, searchFields = DataObjectFields, verb = ifelse(is.null(SearchObject), 'GET', 'POST'), payload = SearchObject)$Objects
  
  # If no results match the query...
  if(length(DataObjects) == 0) return(data.frame(DataObjects))
  
  for(i in 1:length(DataObjects)){
    
    DataObjects[[i]][unlist(lapply(DataObjects[[i]], length) == 0)] <- ''
  }
  
  DataObjects <- jsonlite::fromJSON(jsonlite::toJSON(DataObjects), flatten = T)
  DataObjects <- characterizeDataFrame(DataObjects)
  
  return(DataObjects)
}

# No modidfications needed. Fields will be prepopulated on the module functions.
getDataObject <- function(Module, ObjectName, DataObjectID, DataObjectFields = 'all', EntityID = 1){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  if('all' %in% DataObjectFields){
    DataObjectFields <- getFieldsForObject(Module, ObjectName, EntityID)$Field
  }
  
  DataObjectEndpoint <- paste(ObjectEndpoint, DataObjectID, sep = '/')
  
  DataObject <- makeRequest(endpoint = DataObjectEndpoint, searchFields = DataObjectFields)
  
  DataObject[unlist(lapply(DataObject, length) == 0)] <- ''
  
  DataObject <- as.data.frame(DataObject)
  
  return(DataObject)
}


# Sample: modifyDataObject(EntityID = '4', Module = 'Attendance', ObjectName = 'AttendanceType', DataObjectID = '97', DataObjectFields = 'Description', DataObjectFieldsValues = 'Excused Absent')
modifyDataObject <- function(Module, ObjectName, DataObjectID, DataObjectFields, DataObjectFieldsValues, EntityID = 1){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  Object <- makeRequest(ObjectEndpoint)
  
  DataObjectIdVariable <- names(Object)[[1]]

  DataObjectEndpoint <- paste(ObjectEndpoint, DataObjectID, sep = '/')
  
  DataObjectText <- paste0('list(DataObject = list(', DataObjectIdVariable, ' = ', DataObjectID)
  for(field in DataObjectFields[DataObjectFields != DataObjectIdVariable]){
   
    value <- DataObjectFieldsValues[[which(DataObjectFields == field)]]
                             
    DataObjectText <- paste0(DataObjectText, ', ', field, ' = "', value, '"')
  }
  
  DataObjectText <- paste0(DataObjectText, '))')
  
  DataObject <- eval(parse(text = DataObjectText))
  
  DataObject <- makeRequest(endpoint = DataObjectEndpoint, payload = jsonlite::fromJSON(jsonlite::toJSON(DataObject, pretty = T)), searchFields = union(DataObjectIdVariable, DataObjectFields), verb = 'POST')
  
  return(DataObject %>% as.data.frame(stringsAsFactors = F))
}


createDataObject <- function(Module, ObjectName, DataObjectFields, DataObjectFieldsValues, EntityID = 1){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  DataObjectText <- paste0('list(DataObject = list(')
                           
  DataObjectIdVariable <- paste0(ObjectName, 'ID')
  
  for(field in DataObjectFields){
    
    value <- DataObjectFieldsValues[[which(DataObjectFields == field)]]
    
    DataObjectText <- paste0(DataObjectText, ifelse(field == DataObjectFields[[1]], '', ', '), field, ' = "', value, '"')
  }
  
  DataObjectText <- paste0(DataObjectText, '))')
 
  DataObject <- eval(parse(text = DataObjectText))
  
  DataObject <- makeRequest(endpoint = ObjectEndpoint, payload = jsonlite::fromJSON(jsonlite::toJSON(DataObject, pretty = T)), searchFields = union(DataObjectIdVariable, DataObjectFields), verb = 'PUT')
  
  return((DataObject %>% as.data.frame(stringsAsFactors = F) %>% dplyr::select(DataObjectIdVariable)) %>% bind_cols(DataObject %>% as.data.frame(stringsAsFactors = F) %>% dplyr::select(-DataObjectIdVariable)))
}

deleteDataObject <- function(Module, ObjectName, DataObjectID, EntityID = 1){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  ModuleEndpoint <- paste('Generic', EntityID, Module, sep = '/')
  
  ObjectEndpoint <- paste(ModuleEndpoint, ObjectName, sep = '/')
  
  DataObjectEndpoint <- paste(ObjectEndpoint, DataObjectID, sep = '/')
  
  DataObject <- makeRequest(endpoint = DataObjectEndpoint, verb = 'DELETE')
  
  return(DataObject)
}

generatePkgdownYmlFile <- function(modules){
  
  # Update _pkgdown.yml to aid in reference navigation.
  ymlText <- paste0('url: https://samterfa.github.io/SkywardSDK/
                    
author: Sam Terfa

reference:')
  
  for(module in allModules){
    
  ymlText <- paste0(ymlText,'
 - title: ', stringr::str_to_title(module) ,'
   desc:  Functions involving ', module, '.
   contents:
   - has_concept("', module, '")')
}
  
  writeLines(ymlText, 'pkgdown/_pkgdown.yml')
}

# allModules <- c("Account", "AccountsPayable", "AccountsReceivable", "AccountStructure", "Activity", "API", "Assessment", "Asset", "Attendance", "Base", "BenefitManagement", "Budgeting", "BusinessDataMigration", "Calendar", "Common", "Conversion", "Curriculum", "DataMigrationManager", "Demographics", "Discipline", "District", "Employee", "Enrollment", "EventQueue", "Family", "FeeManagement", "FoodService", "Gradebook", "Grading", "GraduationRequirements", "Guidance", "Health", "Home", "MessageCenter", "MinnehahaCustomization", "Monitor", "MTSS", "OneRoster", "OnlineForm", "Payroll", "PayrollTaxTable", "PerformanceAcknowledgment", "Position", "Purchasing", "Reporting", "Scheduling", "Security", "SkySys", "SpecialEducation", "SpecialPrograms", "Staff", "StaffPlanning", "StateReporting", "StateReportingFederal", "StateReportingMN", "Student", "StudentDataMigration", "SubstituteTracking", "SupportCenter", "TimeOff", "TimeTracking", "Transportation", "Vendor", "Warehouse", "Workflow", "YearEnd")

 allModules <- c("Attendance", "Curriculum", "Demographics", "Discipline", "District",

                "Enrollment", "Family", "GraduationRequirements", "Gradebook", "Grading", "Guidance", "Health", "MessageCenter",

                "OnlineForm", "Reporting", "Scheduling", "Security", "SkySys", "Staff", "StaffPlanning", "Student", "Transportation")

# allModules <- c('Attendance')

# This function generates SDK functions for the Skyward API.
generateAPIfunctions <- function(overwriteAllFunctionsFile = F, overwritePkgdownYmlFile = F, testing = F){
  
  suppressMessages(suppressWarnings(require(dplyr)))
  
  on.exit({suppressWarnings({sink(); sink(); sink(); sink(); sink(); sink(); sink(); sink(); sink(); sink()})})
  
  if(file.exists('allFunctionNames.csv') & overwriteAllFunctionsFile) file.remove('allFunctionNames.csv')
  if(!overwriteAllFunctionsFile){
    
    cat('\nNOT overwriting allFunctions.csv!\n\n')
    
  }else{
    
    cat('\n OVERWRITING allFunctions.csv!\n\n')  
    
    }
  
  if(file.exists('pkgdown/_pkgdown.yml') & overwritePkgdownYmlFile){
    
    file.remove('pkgdown/_pkgdown.yml')
    
  }
  
  # Keep track of all functions made and ensure uniqueness of names by pasting on module name.
  allFunctions <- NULL
  for(module in allModules){
    
    print(paste0(module, ": ", which(allModules == module), " of ", length(allModules)))
    
    if(!testing) sink(file=paste0('R/', module, "Functions.R"))
    
    cat('\n')
    
    allModuleObjects <- getObjectsForModuleAndEntity(Module = module, EntityID = 1)
    
  for(j in 1:nrow(allModuleObjects)){
    
    ######################          for(j in 1:1){
      
      object <- allModuleObjects[j,]
      
      objectName <- object$ObjectName
      
      objectPlural <- paste0(objectName, 's')
      
      objectLastLetter <- substr(objectName, nchar(objectName), nchar(objectName))
      
      if(objectLastLetter == 's') objectPlural <- paste0(objectName, 'es')
                             
      if(objectLastLetter == 'y') objectPlural <- paste0(substr(objectName, 1, nchar(objectName) - 1), 'ies') 
      
      if(objectName == 'Staff') objectPlural <- objectName
      
      if(substr(objectName, nchar(objectName) - 2, nchar(objectName)) == 'Day') objectPlural <- paste0(substr(objectName, 1, nchar(objectName) - 3), 'Days')
      
      objectArticle <- ifelse(tolower(substr(objectName, 1, 1)) %in% c('a', 'e', 'i', 'o', 'u'), 'an', 'a')
        
      allObjectFields <- getFieldsForObject(Module = module, ObjectName = objectName, EntityID = 1)
      
      # Using custom getAllDistricts and getAllEntities functions.
      if(!objectName %in% c('Entity', 'District')){
      
        ######## Get all data objects for an object.
        cat(paste0("#' Get all ", objectPlural, ".\n",  # Title short description
                   "#'\n",
                   "#' This function returns a dataframe of all ", objectPlural, " in the database.\n", # Description
                   "#'\n",
                   "#' @param EntityID The id of the entity. Run \\code{\\link{getAllEntities}} for a list of entities.\n",
                   "#' @param searchConditionsList A list of search conditions to filter results which are joined by the searchConditionsGroupType. Of the form {FieldName} {ConditionType} {SearchCondition}. For example, c('StudentID LessEqual 500', 'LastName Like Ander\\%'). Run \\code{\\link{getAllSearchConditionTypes}} for a list of ConditionTypes. Defaults to NULL (unfiltered).\n",
                   "#' @param searchConditionsGroupType The conjunction which joins multiple searchConditions in the searchConditionsList. Either 'Or' or 'And'. Defaults to 'And'.\n",
                   "#' @param searchSortFieldNamesList The list of fields sort results by. Defaults to NULL (unsorted).\n",
                   "#' @param searchSortFieldNamesDescendingList A list of T/F values corresponding to whether to sort each field in searchSortFieldNamesList in descending order. Defaults to F for each FieldName in searchSortFieldNamesList.\n",
                   "#' @param return{FieldName} A TRUE or FALSE value determining whether or not to return {FieldName} for the given object. Defaults to FALSE for all return fields which for convenience returns all fields for the object.\n",
                   "#' @concept ", module, "\n",
                   "#' @return All ", objectPlural, " in the database.\n",
                   "#' @section References:\n",
                   "#' \\{yourApiUrl\\}/swagger\\cr\\cr\n",
                   "#' \\href{https://help.skyward.com/}{Skyward's Knowledge Hub}\n",
                   "#' @export\n"
        ))
        
        functionName <- paste0('getAll', objectPlural)
        if(functionName %in% allFunctions){
          functionName <- paste0(functionName, module)
        }
        allFunctions <- append(allFunctions, functionName)
        
        cat(paste0('\t', functionName, ' <- function(EntityID = 1, searchConditionsList = NULL, searchConditionsGroupType = "And", searchSortFieldNamesList = NULL, searchSortFieldNamesDescendingList = rep(F, length(searchSortFieldNamesList)), page = 1, pageSize = "100000", '))
                   
        for(fieldName in allObjectFields$Field){
          
          cat(paste0('return', fieldName, ' = F', ifelse(which(allObjectFields$Field == fieldName) < length(allObjectFields$Field), ', ', '){\n\n')))
          
        }
        
        cat('\t\tsuppressMessages(suppressWarnings(require(dplyr)))\n\n')
        
        cat(paste0('\t\tfunctionParams <- as.list(environment())\n\n'))
        
        cat(paste0('\t\tfunctionParams <- functionParams[which(unlist(lapply(functionParams, function(x) length(x) > 0)))]\n\n'))
        
        cat(paste0('\t\tsearchFields <- names(functionParams)[(unlist(lapply(functionParams, function(x) ifelse(length(x) == 1, x == T, F)))) & (names(functionParams) %>% stringr::str_detect("^return"))]\n\n'))
           
        cat(paste0('\t\tif(length(searchFields) == 0) searchFields <- names(functionParams)[names(functionParams) %>% stringr::str_detect("^return")]\n\n'))
        
        cat(paste0('\t\tsearchFields <- searchFields %>% stringr::str_replace("return", "")\n\n'))
        
        cat(paste0('\t\tgetAllDataObjectsForObject("', module, '", "', objectName, '", searchFields, EntityID, searchConditionsList, searchConditionsGroupType, searchSortFieldNamesList, searchSortFieldNamesDescendingList, page, pageSize)\n\n'))
        
        cat('\t}\n\n\n')
      
      } ######## Using custom getAllDistricts and getAllEntities functions
      
      ######## Get specific data objects for an object by id.
      cat(paste0("#' Get a specific ", objectName, "\n",  # Title short description
                 "#'\n",
                 "#' This function returns fields for ", objectArticle, " ", objectName, ".\n", # Description
                 "#'\n",
                 "#' @param ", objectName, "ID The id of the ", objectName,".\\cr Run \\code{\\link{getAll", objectPlural, "}} for a list of ", objectPlural, ".\n",
                 "#' @param EntityID The id of the entity. Run \\code{\\link{getAllEntities}} for a list of entities.\n",
                 "#' @param return{FieldName} A TRUE or FALSE value determining whether or not to return {FieldName} for the given object. Defaults to FALSE for all return fields which for convenience returns all fields for the object.\n",
                 "#' @concept ", module, "\n",
                 "#' @return Details for the ", objectName, ".\n",
                 "#' @section References:\n",
                 "#' \\{yourApiUrl\\}/swagger\\cr\\cr\n",
                 "#' \\href{https://help.skyward.com/}{Skyward's Knowledge Hub}\n",
                 "#' @export\n"
      ))
      
      functionName <- paste0('get', objectName)
      if(functionName %in% allFunctions){
        functionName <- paste0(functionName, module)
      }
      
      allFunctions <- append(allFunctions, functionName)
      
      cat(paste0('\t', functionName, ' <- function(', objectName, 'ID, ', ifelse(objectName == 'Entity', '', 'EntityID = 1, ')))
      
      for(fieldName in allObjectFields$Field){
        
        cat(paste0('return', fieldName, ' = F', ifelse(which(allObjectFields$Field == fieldName) < length(allObjectFields$Field), ', ', '){\n\n')))
        
      }
      
      cat('\t\tsuppressMessages(suppressWarnings(require(dplyr)))\n\n')
      
      cat(paste0('\t\tfunctionParams <- as.list(environment())[-1]\n\n'))
      
      cat(paste0('\t\tfunctionParams <- functionParams[which(unlist(lapply(functionParams, function(x) length(x) > 0)))]\n\n'))
      
      cat(paste0('\t\tsearchFields <- names(functionParams)[(unlist(lapply(functionParams, function(x) ifelse(length(x) == 1, x == T, F)))) & (names(functionParams) %>% stringr::str_detect("^return"))]\n\n'))
      
      cat(paste0('\t\tif(length(searchFields) == 0) searchFields <- names(functionParams)[names(functionParams) %>% stringr::str_detect("^return")]\n\n'))
      
      cat(paste0('\t\tsearchFields <- searchFields %>% stringr::str_replace("return", "")\n\n'))
      
      cat(paste0('\t\tgetDataObject("', module, '",  "', objectName, '", ', objectName, 'ID, searchFields, EntityID)\n\n'))
    
      cat('\t}\n\n\n')
    
      ######## Modify specific data objects for an object by id.
      cat(paste0("#' Modify a specific ", objectName, "\n",  # Title short description
                 "#'\n",
                 "#' This function modifies fields for ", objectArticle, ' ', objectName, ".\n", # Description
                 "#'\n",
                 "#' @param ", objectName, "ID The id of the ", objectName," to be modified.\\cr Run \\code{\\link{getAll", objectPlural, "}} for a list of ", objectName, ifelse(substr(objectName, nchar(objectName), nchar(objectName)) != 's', 's', ''), ".\n",
                 "#' @param EntityID The id of the entity. Run \\code{\\link{getAllEntities}} for a list of entities.\n",
                 "#' @param set{FieldName} Values to set {FieldName} to for the given object. Defaults to NULL for all set fields which does not set the field's value.\n",
                 "#' @concept ", module, "\n",
                 "#' @return Details of the modified ", objectName, ".\n",
                 "#' @section References:\n",
                 "#' \\{yourApiUrl\\}/swagger\\cr\\cr\n",
                 "#' \\href{https://help.skyward.com/}{Skyward's Knowledge Hub}\n",
                 "#' @export\n"
      ))
      
      allObjectFieldsAndInfo <- getFieldsForObject(module, objectName, 1) %>% dplyr::filter(ReadOnly == F)
      
      functionName <- paste0('modify', objectName)
      if(functionName %in% allFunctions){
        functionName <- paste0(functionName, module)
      }
      
      allFunctions <- append(allFunctions, functionName)
      
      if(objectName == 'Entity'){
        cat(paste0('\t', functionName, ' <- function(', objectName, 'ID'))
      }else{
        cat(paste0('\t', functionName, ' <- function(', objectName, 'ID, EntityID = 1'))
      }
      
      for(field in allObjectFieldsAndInfo$Field){
        
          cat(paste0(', set', field, ' = NULL'))
  
      }
  
      cat('){\n\n')
      
      cat('\t\tsuppressMessages(suppressWarnings(require(dplyr)))\n\n')
          
      cat(paste0('\t\tfunctionParams <- as.list(environment())[-(1:2)]\n\n'))
      
      cat(paste0('\t\tfunctionParams <- functionParams[which(unlist(lapply(functionParams, function(x) length(x) > 0)))]\n\n'))
      
      cat(paste0('\t\tnames(functionParams) <- names(functionParams) %>% stringr::str_replace("set", "")\n\n'))
      
      cat(paste0('\t\tmodifyDataObject("', module, '",  "', objectName, '", ', objectName, 'ID, names(functionParams), functionParams, EntityID)\n\n'))
      
      cat('\t}\n\n\n')
      
      ######## Create new data object for an object.
      cat(paste0("#' Create new ", objectName, ".\n",  # Title short description
                 "#'\n",
                 "#' This function creates a new ", objectName, ".\n", # Description
                 "#'\n"))
      cat("#' @param EntityID The id of the entity. Run \\code{\\link{getAllEntities}} for a list of entities.\n")
      cat("#' @param set{FieldName} Values to set {FieldName} to for the given object. Defaults to NULL for all set fields which does not set the field's value.\n")
      cat(paste0("#' @concept ", module, "\n",
                 "#' @return The fields used to define the newly created ", objectName, ".\n",
                 "#' @section References:\n",
                 "#' \\{yourApiUrl\\}/swagger\\cr\\cr\n",
                 "#' \\href{https://help.skyward.com/}{Skyward's Knowledge Hub}\n",
                 "#' @export\n"
      ))
      
      functionName <- paste0('create', objectName)
      if(functionName %in% allFunctions){
        functionName <- paste0(functionName, module)
      }
      
      allFunctions <- append(allFunctions, functionName)
      
      cat(paste0('\t', functionName, ' <- function(EntityID = 1'))
      
      for(field in allObjectFieldsAndInfo$Field){
        
        cat(paste0(', set', field, ' = NULL'))
        
      }
      
      cat('){\n\n')
      
      if(objectName %in% c('Entity', 'District')){
        
        cat("\t\tstop('Cannot create a District or Entity via the API!')\n\n")
        
      }else{
      
        cat('\t\tsuppressMessages(suppressWarnings(require(dplyr)))\n\n')
        
        cat(paste0('\t\tfunctionParams <- as.list(environment())[-1]\n\n'))
        
        cat(paste0('\t\tfunctionParams <- functionParams[which(unlist(lapply(functionParams, function(x) length(x) > 0)))]\n\n'))
        
        cat(paste0('\t\tnames(functionParams) <- names(functionParams) %>% stringr::str_replace("set", "")\n\n'))
        
        cat(paste0('\t\tcreateDataObject("', module, '",  "', objectName, '", names(functionParams), functionParams, EntityID)\n\n'))
      
      }
      
      cat('\t}\n\n\n')
      
      ######## Delete specific data objects for an object by id.
      cat(paste0("#' Delete a specific ", objectName, "\n",  # Title short description
                 "#'\n",
                 "#' This function deletes ", objectArticle, " ", objectName, ".\n", # Description
                 "#'\n",
                 "#' @param ", objectName, "ID The id of the ", objectName,".\\cr Run \\code{\\link{getAll", objectPlural, "}} for a list of ", objectPlural, ".\n",
                 "#' @param EntityID The id of the entity. Run \\code{\\link{getAllEntities}} for a list of entities.\n",
                 "#' @concept ", module, "\n",
                 "#' @return The id of the deleted ", objectName, ".\n",
                 "#' @section References:\n",
                 "#' \\{yourApiUrl\\}/swagger\\cr\\cr\n",
                 "#' \\href{https://help.skyward.com/}{Skyward's Knowledge Hub}\n",
                 "#' @export\n"
      ))
      
      functionName <- paste0('delete', objectName)
      if(functionName %in% allFunctions){
        functionName <- paste0(functionName, module)
      }
      
      allFunctions <- append(allFunctions, functionName)
      
      if(objectName == 'Entity'){
        cat(paste0('\t', functionName, ' <- function(', objectName, 'ID){\n\n'))
      }else{
        cat(paste0('\t', functionName, ' <- function(', objectName, 'ID, EntityID = 1){\n\n'))
      }
      
      if(objectName %in% c('Entity', 'District')){
     
        cat("\t\tstop('Cannot delete a District or Entity via the API!')\n\n")
        
      }else{
        
        cat('\t\tsuppressMessages(suppressWarnings(require(dplyr)))\n\n')
        
        cat(paste0('\t\tdeleteDataObject("', module, '",  "', objectName, '", ', objectName, 'ID, EntityID)\n\n'))
        
      }
        
      cat('\t}\n\n\n')
    }
    
    sink()
    
    beepr::beep(2)
    
    if(overwriteAllFunctionsFile) readr::write_csv(tibble(Functions = allFunctions), 'allFunctionNames.csv', append = T) 
  }
  
  if(overwritePkgdownYmlFile) generatePkgdownYmlFile(allModules)
}
samterfa/SkywardSDK documentation built on Oct. 13, 2020, 6:53 a.m.