diff --git a/DESCRIPTION b/DESCRIPTION index fb085a5..981fe5f 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -4,8 +4,8 @@ Title: Interface with Azure Machine Learning datasets and web services Description: Functions and datasets to support Azure Machine Learning. This allows you to interact with datasets, as well as publish and consume R functions as API services. -Version: 0.2.6 -Date: 2015-12-18 +Version: 0.2.7 +Date: 2015-12-19 Authors@R: c( person("Raymond", "Laghaeian", role=c("aut", "cre"), email="raymondl@microsoft.com"), person(family="Microsoft Corporation", role="cph"), diff --git a/NAMESPACE b/NAMESPACE index 3d92d59..4da06b0 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -19,11 +19,13 @@ export(is.Endpoint) export(is.Service) export(is.Workspace) export(publishWebService) +export(read.AzureML.config) export(refresh) export(services) export(updateWebService) export(upload.dataset) export(workspace) +export(write.AzureML.config) import(codetools) importFrom(base64enc,base64encode) importFrom(curl,curl) diff --git a/R/config.R b/R/config.R new file mode 100644 index 0000000..6807060 --- /dev/null +++ b/R/config.R @@ -0,0 +1,79 @@ +validate.AzureML.config <- function(config = getOption("AzureML.config"), stopOnError = FALSE){ + # Stop if the config file is missing + if(!file.exists(config)) { + msg <- sprintf("config file is missing: '%s'", config) + if(stopOnError) + stop(msg, call. = FALSE) + else + return(simpleError(msg)) + } + + # Stop if the config is a directory, not a file + if(file.info(config)$isdir){ + msg <- paste( + "The config argument should point to a file.", + sprintf(" You provided a directory (%s)", + normalizePath(config, winslash = "/", mustWork = FALSE) + ), sep = "\n" + ) + if(stopOnError) + stop(msg, call. = FALSE) + else + return(simpleError(msg)) + } + TRUE +} + +#' Reads settings from configuration file in JSON format. +#' +#' @inheritParams workspace +#' +#' @export +#' @seealso write.AzureML.config +#' @seealso workspace +read.AzureML.config <- function(config = getOption("AzureML.config")){ + z <- tryCatch(fromJSON(file(config)), + error = function(e)e + ) + # Error check the settings file for invalid JSON + if(inherits(z, "error")) { + msg <- sprintf("Your config file contains invalid json", config) + msg <- paste(msg, z$message, sep = "\n\n") + stop(msg, call. = FALSE) + } + z +} + +#' Writes settings to configuration file. +#' +#' @inheritParams workspace +#' @param file either a character string naming a file or a connection open for writing. "" indicates output to the console. +#' +#' @rdname read.AzureML.config +#' +#' @export +#' @seealso write.AzureML.config +#' @seealso workspace +write.AzureML.config <- function(id = NULL, auth = NULL, + api_endpoint = NULL, + management_endpoint = NULL, + file = ""){ + # Construct list + x <- list( + id = id, + authorization_token = auth, + api_endpoint = api_endpoint, + management_endpoint = management_endpoint + ) + # Remove null values + conf <- list( + workspace = x[!sapply(x, is.null)] + ) + # Convert to JSON + js <- jsonlite::toJSON(conf, pretty = TRUE) + if(!missing(file) && !is.null(file)) { + writeLines(js, con = file) + } else { + js + } +} diff --git a/R/internal.R b/R/internal.R index b43209c..be27861 100644 --- a/R/internal.R +++ b/R/internal.R @@ -77,27 +77,32 @@ urlconcat <- function(a,b) get_datasets <- function(ws) { h = new_handle() - handle_setheaders(h, .list=ws$.headers) - r = curl(sprintf("%s/workspaces/%s/datasources", ws$.studioapi, ws$id), handle=h) - on.exit(close(r)) - x = tryCatch(fromJSON(readLines(r, warn=FALSE)), error=invisible) + handle_setheaders(h, .list = ws$.headers) + uri <- sprintf("%s/workspaces/%s/datasources", ws$.studioapi, ws$id) + r <- try_fetch(uri = uri, handle = h, delay = 0.25, tries = 3) + if(inherits(r, "error")){ + msg <- paste("No results returned from datasets(ws).", + "Please check your workspace credentials and api_endpoint are correct.") + stop(msg) + } + x <- fromJSON(rawToChar(r$content)) if(is.null(x) || is.na(x$Name[1])){ x = data.frame() class(x) = c("Datasets", "data.frame") return(x) } # Use strict variable name matching to look up data - d = x[,"DownloadLocation"] - x$DownloadLocation = paste(d[,"BaseUri"], - d[,"Location"], - d[,"AccessCredential"], sep="") + d = x[, "DownloadLocation"] + x$DownloadLocation = paste0(d[, "BaseUri"], + d[, "Location"], + d[, "AccessCredential"]) d = x[,"VisualizeEndPoint"] - x$VisualizeEndPoint = paste(d[,"BaseUri"], - d[,"AccessCredential"], sep="") + x$VisualizeEndPoint = paste0(d[, "BaseUri"], + d[, "AccessCredential"]) d = x[,"SchemaEndPoint"] - x$SchemaEndPoint = paste(d[,"BaseUri"], - d[,"Location"], - d[,"AccessCredential"], sep="") + x$SchemaEndPoint = paste0(d[, "BaseUri"], + d[, "Location"], + d[, "AccessCredential"]) class(x) = c("Datasets", "data.frame") x } @@ -158,18 +163,18 @@ get_dataset <- function(x, h, quote = "\"", ...) if(tolower(x$DataTypeId) == "zip") conn = "rb" uri = curl(x$DownloadLocation, handle=h, open=conn) on.exit(tryCatch(close(uri), error=invisible), add=TRUE) - - # Existence of DataTypeId, DowloadLocation guaranteed by caller - switch(tolower(x$DataTypeId), - arff = read.arff(uri), - plaintext = paste(readLines(uri, warn=FALSE), collapse="\n"), - generictsvnoheader = read.table(uri, sep="\t", header=FALSE, quote, ...), - generictsv = read.table(uri, sep="\t", header=TRUE, quote, ...), - genericcsvnoheader = read.table(uri, sep=",", header=FALSE, quote, ...), - genericcsv = read.table(uri, sep=",", header=TRUE, quote, ...), - zip = readBin(uri, what="raw", n=x$Size, ...), - stop("unsupported data type: '",x$DataTypeId,"'") - ) + + # Existence of DataTypeId, DowloadLocation guaranteed by caller + switch(tolower(x$DataTypeId), + arff = read.arff(uri), + plaintext = paste(readLines(uri, warn=FALSE), collapse="\n"), + generictsvnoheader = read.table(uri, sep="\t", header=FALSE, quote, ...), + generictsv = read.table(uri, sep="\t", header=TRUE, quote, ...), + genericcsvnoheader = read.table(uri, sep=",", header=FALSE, quote, ...), + genericcsv = read.table(uri, sep=",", header=TRUE, quote, ...), + zip = readBin(uri, what="raw", n=x$Size, ...), + stop("unsupported data type: '",x$DataTypeId,"'") + ) } @@ -205,7 +210,7 @@ packageEnv <- function(exportenv, packages=NULL, version="3.1.0") setwd(d) # save export environment to an RData file save(exportenv, file="env.RData") - + # Package up dependencies if(!is.null(packages)) { @@ -214,9 +219,9 @@ packageEnv <- function(exportenv, packages=NULL, version="3.1.0") p = paste(d,"packages",sep="/") tryCatch(dir.create(p), warning=function(e) stop(e)) tryCatch(makeRepo(pkgDep(packages, repos=re, suggests=FALSE), path=p, re, type="win.binary", Rversion=version), - error=function(e) stop(e)) + error=function(e) stop(e)) } - + z = try({ zip(zipfile="export.zip", files=dir(), flags = "-r9Xq") }) diff --git a/R/makeConfig.R b/R/makeConfig.R deleted file mode 100644 index decd5a9..0000000 --- a/R/makeConfig.R +++ /dev/null @@ -1,19 +0,0 @@ -makeConfig <- function(id = NULL, authorization_token = NULL, - api_endpoint = NULL, management_endpoint = NULL, file){ - x <- list( - id = id, - authorization_token = authorization_token, - api_endpoint = api_endpoint, - management_endpoint = management_endpoint - ) - conf <- list( - workspace = x[!sapply(x, is.null)] - ) - js <- jsonlite::toJSON(conf, pretty = TRUE) - # browser() - if(!missing(file) && !is.null(file)) { - writeLines(js, con = file) - } else { - js - } -} diff --git a/R/options.R b/R/options.R new file mode 100644 index 0000000..1f230a7 --- /dev/null +++ b/R/options.R @@ -0,0 +1,2 @@ +AzureML.config.default <- "~/.azureml/settings.json" +options(AzureML.config = AzureML.config.default) \ No newline at end of file diff --git a/R/workspace.R b/R/workspace.R index 135fca7..dff4384 100644 --- a/R/workspace.R +++ b/R/workspace.R @@ -25,17 +25,20 @@ default_api <- function(api_endpoint = "https://studioapi.azureml.net"){ defaults <- list( + "https://studio.azureml.net" = list( + api_endpoint = "https://studioapi.azureml.net", + management_endpoint = "https://management.azureml.net", + studioapi = "https://studioapi.azureml.net/api" + ), "https://studioapi.azureml.net" = list( api_endpoint = "https://studioapi.azureml.net", management_endpoint = "https://management.azureml.net", studioapi = "https://studioapi.azureml.net/api" - - ), "https://studioapi.azureml-int.net" = list( - + ), + "https://studioapi.azureml-int.net" = list( api_endpoint = "https://studio.azureml-int.net", management_endpoint = "https://management.azureml-int.net", studioapi = "https://studioapi.azureml-int.net/api" - ) ) @@ -55,7 +58,7 @@ default_api <- function(api_endpoint = "https://studioapi.azureml.net"){ #' @param auth Optional authorization token from ML studio -> settings -> AUTHORIZATION TOKENS #' @param api_endpoint Optional AzureML API web service URI. Defaults to \url{https://studio.azureml.net} if not provided and not specified in config. See note. #' @param management_endpoint Optional AzureML management web service URI. Defaults to \url{https://management.azureml.net} if not provided and not specified in config. See note. -#' @param config Optional settings file containing id and authorization info. Used if any of the other arguments are missing. The default config file is \code{~/.azureml/settings.json}. +#' @param config Optional settings file containing id and authorization info. Used if any of the other arguments are missing. The default config file is \code{~/.azureml/settings.json}, but you can change this location by setting \code{options(AzureML.config = "newlocation")} #' #' @note If any of the \code{id}, \code{auth}, \code{api_endpoint} or \code{management_endpoint} arguments are missing, the function attempts to read values from the \code{config} file with JSON format: \preformatted{ #' {"workspace":{ @@ -82,54 +85,70 @@ default_api <- function(api_endpoint = "https://studioapi.azureml.net"){ #' @seealso \code{\link{datasets}}, \code{\link{experiments}}, \code{\link{refresh}}, #' \code{\link{services}}, \code{\link{consume}}, \code{\link{publishWebService}} workspace <- function(id, auth, api_endpoint, management_endpoint, - config="~/.azureml/settings.json") + config = getOption("AzureML.config")) { - if(missing(id) || missing(auth) || missing(api_endpoint) || missing(management_endpoint)) - { - if(!file.exists(config)) stop(sprintf("config file is missing: '%s'", config)) - settings = tryCatch(fromJSON(file(config)), - error = function(e)e - ) - if(inherits(settings, "error")) { - msg <- sprintf("Your config file contains invalid json", config) - msg <- paste(msg, settings$message, sep = "\n\n") - stop(msg, call. = FALSE) - } + + + # If workspace_id or auth are missing, read from config. Stop if unavailable. + if(missing(id) || missing(auth)) { + x <- validate.AzureML.config(config, stopOnError = TRUE) + if(inherits(x, "error")) stop(x$message) + settings <- read.AzureML.config(config) + if(missing(id)){ id <- settings[["workspace"]][["id"]] } if(missing(auth)){ auth <- settings[["workspace"]][["authorization_token"]] } - if(missing(api_endpoint)){ - api_endpoint <- settings[["workspace"]][["api_endpoint"]] - } - if(missing(management_endpoint)){ - management_endpoint <- settings[["workspace"]][["management_endpoint"]] + } + + # If workspace_id or auth are missing, read from config, if available. + if(missing(api_endpoint) || missing(management_endpoint)){ + x <- validate.AzureML.config(config, stopOnError = FALSE) + if(!inherits(x, "error")){ + settings <- read.AzureML.config(config) + + if(missing(api_endpoint)){ + api_endpoint <- settings[["workspace"]][["api_endpoint"]] + } + if(missing(management_endpoint)){ + management_endpoint <- settings[["workspace"]][["management_endpoint"]] + } } } - default_api <- if(is.null(api_endpoint)) { - default_api() + + # Assign a default api_endpoint if this was not provided + default_api <- if(missing(api_endpoint) || is.null(api_endpoint)) { + default_api() } else { default_api(api_endpoint) } - if(is.null(api_endpoint)) api_endpoint <- default_api[["api_endpoint"]] - if(is.null(management_endpoint)) management_endpoint <- default_api[["management_endpoint"]] + if(missing(api_endpoint) || is.null(api_endpoint)){ + api_endpoint <- default_api[["api_endpoint"]] + } - # test to see if api_endpoint is a valid url + # Assign a default management_endpoint if this was not provided + if(missing(management_endpoint) || is.null(management_endpoint)){ + management_endpoint <- default_api[["management_endpoint"]] + } + + # Test to see if api_endpoint is a valid url resp <- tryCatch( suppressWarnings(curl::curl_fetch_memory(api_endpoint)), error = function(e)e ) if(inherits(resp, "error")) stop("Invalid api_endpoint: ", api_endpoint) - # test to see if api_endpoint is a valid url + # Test to see if management_endpoint is a valid url resp <- tryCatch( suppressWarnings(curl::curl_fetch_memory(management_endpoint)), error = function(e)e ) if(inherits(resp, "error")) stop("Invalid management_endpoint: ", management_endpoint) + # It seems all checks passed. Now construct the Workspace object + e <- new.env() class(e) <- "Workspace" e$id <- id @@ -143,9 +162,9 @@ workspace <- function(id, auth, api_endpoint, management_endpoint, `x-ms-client-session-id` = "DefaultSession", `x-ms-metaanalytics-authorizationtoken` = auth ) - delayedAssign("experiments", get_experiments(e), assign.env=e) - delayedAssign("datasets", get_datasets(e), assign.env=e) - delayedAssign("services", services(e), assign.env=e) + delayedAssign("experiments", get_experiments(e), assign.env = e) + delayedAssign("datasets", get_datasets(e), assign.env = e) + delayedAssign("services", services(e), assign.env = e) e } diff --git a/R/zzz_test_helpers.R b/R/zzz_test_helpers.R new file mode 100644 index 0000000..f541385 --- /dev/null +++ b/R/zzz_test_helpers.R @@ -0,0 +1,11 @@ +# This function is used in unit testing to skip tests if the config file is missing +# +skip_if_missing_config <- function(f){ + if(!file.exists(f)) { + msg <- paste("To run tests, add a file ~/.azureml/settings.json containing AzureML keys.", + "See ?workspace for help", + sep = "\n") + message(msg) + skip("settings.json file is missing") + } +} diff --git a/man/read.AzureML.config.Rd b/man/read.AzureML.config.Rd new file mode 100644 index 0000000..572c66a --- /dev/null +++ b/man/read.AzureML.config.Rd @@ -0,0 +1,40 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/config.R +\name{read.AzureML.config} +\alias{read.AzureML.config} +\alias{write.AzureML.config} +\title{Reads settings from configuration file in JSON format.} +\usage{ +read.AzureML.config(config = getOption("AzureML.config")) + +write.AzureML.config(id = NULL, auth = NULL, api_endpoint = NULL, + management_endpoint = NULL, file = "") +} +\arguments{ +\item{config}{Optional settings file containing id and authorization info. Used if any of the other arguments are missing. The default config file is \code{~/.azureml/settings.json}, but you can change this location by setting \code{options(AzureML.config = "newlocation")}} + +\item{id}{Optional workspace id from ML studio -> settings -> WORKSPACE ID} + +\item{auth}{Optional authorization token from ML studio -> settings -> AUTHORIZATION TOKENS} + +\item{api_endpoint}{Optional AzureML API web service URI. Defaults to \url{https://studio.azureml.net} if not provided and not specified in config. See note.} + +\item{management_endpoint}{Optional AzureML management web service URI. Defaults to \url{https://management.azureml.net} if not provided and not specified in config. See note.} + +\item{file}{either a character string naming a file or a connection open for writing. "" indicates output to the console.} +} +\description{ +Reads settings from configuration file in JSON format. + +Writes settings to configuration file. +} +\seealso{ +write.AzureML.config + +workspace + +write.AzureML.config + +workspace +} + diff --git a/man/workspace.Rd b/man/workspace.Rd index 9d49130..1f8801a 100644 --- a/man/workspace.Rd +++ b/man/workspace.Rd @@ -5,7 +5,7 @@ \title{Create a reference to an AzureML Studio workspace.} \usage{ workspace(id, auth, api_endpoint, management_endpoint, - config = "~/.azureml/settings.json") + config = getOption("AzureML.config")) } \arguments{ \item{id}{Optional workspace id from ML studio -> settings -> WORKSPACE ID} @@ -16,7 +16,7 @@ workspace(id, auth, api_endpoint, management_endpoint, \item{management_endpoint}{Optional AzureML management web service URI. Defaults to \url{https://management.azureml.net} if not provided and not specified in config. See note.} -\item{config}{Optional settings file containing id and authorization info. Used if any of the other arguments are missing. The default config file is \code{~/.azureml/settings.json}.} +\item{config}{Optional settings file containing id and authorization info. Used if any of the other arguments are missing. The default config file is \code{~/.azureml/settings.json}, but you can change this location by setting \code{options(AzureML.config = "newlocation")}} } \value{ An R environment of class \code{Workspace} containing at least the following objects: diff --git a/tests/testthat/test-1-workspace.R b/tests/testthat/test-1-workspace.R index 70da399..1ae0f37 100644 --- a/tests/testthat/test-1-workspace.R +++ b/tests/testthat/test-1-workspace.R @@ -1,58 +1,85 @@ if(interactive()) library("testthat") -settingsFile <- "~/.azureml/settings.json" -if(file.exists(settingsFile)) -{ - context("Connect to workspace") + +settingsFile <- AzureML.config.default + +# ------------------------------------------------------------------------ + +context("workspace - connect to workspace") + +test_that("Can connect to workspace with supplied id and auth", { + AzureML:::skip_if_missing_config(settingsFile) + + js <- read.AzureML.config(settingsFile) + id <- js$workspace$id + auth <- js$workspace$authorization_token + + expect_true(!is.null(id)) + expect_true(!is.null(auth)) + + ws <- workspace(id, auth) + + expect_is(ws, c("Workspace")) + expect_equal(ls(ws), c("datasets", "experiments", "id", "services")) + expect_equal(ws$id, id) +}) + +test_that("Can connect to workspace with config file", { + AzureML:::skip_if_missing_config(settingsFile) + + ws <- workspace() - test_that("Can connect to workspace with supplied id and auth", { - js <- jsonlite::fromJSON(settingsFile) - id <- js$workspace$id - auth <- js$workspace$authorization_token - - expect_true(!is.null(id)) - expect_true(!is.null(auth)) - - ws <- workspace(id, auth) - - expect_is(ws, c("Workspace")) - expect_equal(ls(ws), c("datasets", "experiments", "id", "services")) - expect_equal(ws$id, id) - }) + expect_is(ws, c("Workspace")) + expect_equal(ls(ws), c("datasets", "experiments", "id", "services")) +}) + + +test_that("Can connect to workspace with no config file", { + # AzureML:::skip_if_missing_config(settingsFile) - test_that("Can connect to workspace with config file", { - skip_on_cran() - skip_on_travis() - - ws <- workspace() - - expect_is(ws, c("Workspace")) - expect_equal(ls(ws), c("datasets", "experiments", "id", "services")) - }) + opts <- getOption("AzureML.config") + options(AzureML.config = tempfile(fileext = ".tmp")) + on.exit(options(AzureML.config = opts)) -} else { - message("To run tests, add a file ~/.azureml/settings.json containing AzureML keys, see ?workspace for help") - message("No tests ran") -} + expect_error( + ws <- workspace(), + "config file is missing" + ) + expect_is(workspace("x", "y"), "Workspace") + expect_equal({ws <- workspace("x", "y"); ls(ws)}, + c("datasets", "experiments", "id", "services")) +}) + -context("Reading from settings.json file") -test_that("Add api_endpoint and management_endpoint if missing from config", { +# ------------------------------------------------------------------------ + +context("workspace - reading from settings.json file") + +test_that("workspace() adds api_endpoint and management_endpoint if missing from config", { tf <- tempfile(fileext = ".json") on.exit(unlink(tf)) - makeConfig("x", "y", file = tf) + write.AzureML.config("x", "y", file = tf) ws <- workspace(config = tf) expect_equal(ws$id, "x") - expect_equal(ws$.api_endpoint, default_api(ws$.api_endpoint)[["api_endpoint"]]) - expect_equal(ws$.management_endpoint, default_api(ws$.api_endpoint)[["management_endpoint"]]) + expect_equal( + ws$.api_endpoint, + default_api(ws$.api_endpoint)[["api_endpoint"]] + ) + expect_equal( + ws$.management_endpoint, + default_api(ws$.api_endpoint)[["management_endpoint"]] + ) }) -test_that("Add api_endpoint and management_endpoint if missing from config", { - expect_error(workspace(config = "file_does_not_exist"), - "config file is missing: 'file_does_not_exist'") +test_that("workspace() throws helpful error if config file does not exist", { + expect_error( + workspace(config = "file_does_not_exist"), + "config file is missing: 'file_does_not_exist'" + ) }) -test_that("Throws helpful error if config is invalid json", { +test_that("workspace() throws helpful error if config is invalid json", { tf <- tempfile(fileext = ".json") on.exit(unlink(tf)) writeLines("garbage", con = tf) diff --git a/tests/testthat/test-2-datasets-upload-download-delete.R b/tests/testthat/test-2-datasets-upload-download-delete.R index aac49fc..7d79233 100644 --- a/tests/testthat/test-2-datasets-upload-download-delete.R +++ b/tests/testthat/test-2-datasets-upload-download-delete.R @@ -1,42 +1,48 @@ if(interactive()) library("testthat") -settingsFile <- "~/.azureml/settings.json" -if(file.exists(settingsFile)) -{ - context("Upload and delete dataset") - ws <- workspace() +settingsFile <- AzureML.config.default + +context("Upload and delete dataset") + +test_that("datasets(ws) returns results", { + AzureML:::skip_if_missing_config(settingsFile) - timestamped_name <- paste0("dataset-test-upload-", - format(Sys.time(), format="%Y-%m-%d--%H-%M-%S")) - - test_that("Can upload dataset to workspace", { - upload.dataset(airquality, ws, timestamped_name) - ds <- datasets(ws, filter = "my") - expect_true(timestamped_name %in% ds$Name) - }) + ws <<- workspace() - test_that("Uploading dataset with duplicate name gives helpful error", { - expect_error(upload.dataset(airquality, ws, timestamped_name), - sprintf("A dataset with the name '%s' already exists in AzureML", timestamped_name) - ) - }) - - test_that("Can download dataset", { - dl <- download.datasets(ws, name=timestamped_name) - expect_equal(dl, airquality) - }) - - test_that("Can delete dataset from workspace", { - z <- delete.datasets(ws, timestamped_name) - expect_true(timestamped_name %in% z$Name && z$Deleted[z$Name == timestamped_name]) - # Force refresh - sometime this fails in non-interactive - Sys.sleep(1); refresh(ws, what = "datasets") - ds <- datasets(ws, filter = "my") - expect_false(timestamped_name %in% ds$Name) - }) - -} else -{ - message("To run tests, add a file ~/.azureml/settings.json containing AzureML keys, see ?workspace for help") - message("No tests ran") -} + x <- datasets(ws) + expect_is(x, "data.frame") +}) + +timestamped_name <- paste0("dataset-test-upload-", + format(Sys.time(), format="%Y-%m-%d--%H-%M-%S")) + +test_that("Can upload dataset to workspace", { + AzureML:::skip_if_missing_config(settingsFile) + upload.dataset(airquality, ws, timestamped_name) + ds <- datasets(ws, filter = "my") + expect_true(timestamped_name %in% ds$Name) +}) + +test_that("Uploading dataset with duplicate name gives helpful error", { + AzureML:::skip_if_missing_config(settingsFile) + expect_error(upload.dataset(airquality, ws, timestamped_name), + sprintf("A dataset with the name '%s' already exists in AzureML", timestamped_name) + ) +}) + +test_that("Can download dataset", { + AzureML:::skip_if_missing_config(settingsFile) + dl <- download.datasets(ws, name=timestamped_name) + expect_equal(dl, airquality) +}) + +test_that("Can delete dataset from workspace", { + AzureML:::skip_if_missing_config(settingsFile) + z <- delete.datasets(ws, timestamped_name) + expect_true(timestamped_name %in% z$Name && z$Deleted[z$Name == timestamped_name]) + # Force refresh - sometime this fails in non-interactive + Sys.sleep(1); refresh(ws, what = "datasets") + ds <- datasets(ws, filter = "my") + expect_true(nrow(ds) == 0 || !timestamped_name %in% ds$Name) +}) + diff --git a/tests/testthat/test-3-experiments-download.R b/tests/testthat/test-3-experiments-download.R index 0c91afb..3d8620c 100644 --- a/tests/testthat/test-3-experiments-download.R +++ b/tests/testthat/test-3-experiments-download.R @@ -4,48 +4,43 @@ if(interactive()) library("testthat") -settingsFile <- "~/.azureml/settings.json" -if(file.exists(settingsFile)) -{ - context("Read dataset from experiment") - - test_that("Can read intermediate dataset from workspace", { - js <- jsonlite::fromJSON(settingsFile) - id <- js$workspace$id - auth <- js$workspace$authorization_token - exp_id <- js$workspace$exp_id - node_id <- js$workspace$node_id - - if(is.null(exp_id) || is.null(node_id)) skip("exp_id or node_id not available") - - ws <- workspace() - - we <- experiments(ws) - expect_is(we, "Experiments") - expect_is(we, "data.frame") - - expect_identical(we, ws$experiments) - - - en <- we$Description - expect_is(en, "character") - expect_true(length(en) > 0) - - expect_true(exp_id %in% we$ExperimentId) - idx <- match(exp_id, we$ExperimentId) - experiment = experiments(ws)[idx, ] - class(experiment) - expect_is(experiment, "Experiments") - expect_is(experiment, "data.frame") - - frame = download.intermediate.dataset(ws, experiment = exp_id, node_id = node_id, - port_name='Results dataset', - data_type_id='GenericCSV') - - expect_is(frame, "data.frame") - expect_true(nrow(frame) > 1) - }) -} else { - message("To run tests, add a file ~/.azureml/settings.json containing AzureML keys, see ?workspace for help") - message("No tests ran") -} +settingsFile <- AzureML.config.default +context("Read dataset from experiment") + +test_that("Can read intermediate dataset from workspace", { + AzureML:::skip_if_missing_config(settingsFile) + js <- jsonlite::fromJSON(settingsFile) + id <- js$workspace$id + auth <- js$workspace$authorization_token + exp_id <- js$workspace$exp_id + node_id <- js$workspace$node_id + + if(is.null(exp_id) || is.null(node_id)) skip("exp_id or node_id not available") + + ws <- workspace() + + we <- experiments(ws) + expect_is(we, "Experiments") + expect_is(we, "data.frame") + + expect_identical(we, ws$experiments) + + + en <- we$Description + expect_is(en, "character") + expect_true(length(en) > 0) + + expect_true(exp_id %in% we$ExperimentId) + idx <- match(exp_id, we$ExperimentId) + experiment = experiments(ws)[idx, ] + class(experiment) + expect_is(experiment, "Experiments") + expect_is(experiment, "data.frame") + + frame = download.intermediate.dataset(ws, experiment = exp_id, node_id = node_id, + port_name='Results dataset', + data_type_id='GenericCSV') + + expect_is(frame, "data.frame") + expect_true(nrow(frame) > 1) +}) diff --git a/tests/testthat/test-4-download-each-dataset-type.R b/tests/testthat/test-4-download-each-dataset-type.R index a942b67..248fd4a 100644 --- a/tests/testthat/test-4-download-each-dataset-type.R +++ b/tests/testthat/test-4-download-each-dataset-type.R @@ -1,46 +1,41 @@ if(interactive()) library("testthat") -settingsFile <- "~/.azureml/settings.json" -if(file.exists(settingsFile)) -{ - context("Download one file of each DataTypeId") +settingsFile <- AzureML.config.default +context("Download one file of each DataTypeId") - ws <- workspace() - ds <- datasets(ws, filter = "samples") - ds$Name - testIdx <- grepl("[Tt]est", ds$Name) - ds <- ds[!testIdx, ] - unique(ds$DataTypeId) +ws <- workspace() +ds <- datasets(ws, filter = "samples") +testIdx <- grepl("[Tt]est", ds$Name) +ds <- ds[!testIdx, ] +unique(ds$DataTypeId) - oneOfEach <- do.call( - rbind, - lapply( - split(ds, ds$DataTypeId), - function(x){ - x[which.min(x$Size), ] - } - ) +oneOfEach <- do.call( + rbind, + lapply( + split(ds, ds$DataTypeId), + function(x){ + x[which.min(x$Size), ] + } ) +) - Zip <- oneOfEach[oneOfEach$DataTypeId %in% c("Zip"), ] - oneOfEach <- oneOfEach[!oneOfEach$DataTypeId %in% c("Zip"), ] - oneOfEach$DataTypeId +Zip <- oneOfEach[oneOfEach$DataTypeId %in% c("Zip"), ] +oneOfEach <- oneOfEach[!oneOfEach$DataTypeId %in% c("Zip"), ] +oneOfEach$DataTypeId - for(type in oneOfEach$DataTypeId){ - test_that(sprintf("Can download dataset of type %s", type), { - dl <- download.datasets(ws, name = oneOfEach$Name[oneOfEach$DataTypeId == type]) - expect_is(dl, "data.frame") - expect_true(nrow(dl) > 0) - }) - } - +for(type in oneOfEach$DataTypeId){ + test_that(sprintf("Can download dataset of type %s", type), { + AzureML:::skip_if_missing_config(settingsFile) + dl <- download.datasets(ws, name = oneOfEach$Name[oneOfEach$DataTypeId == type]) + expect_is(dl, "data.frame") + expect_true(nrow(dl) > 0) + }) +} + +type <- "zip" +test_that(sprintf("Can download dataset of type %s", type), { + AzureML:::skip_if_missing_config(settingsFile) dl <- download.datasets(ws, Zip) class(dl) expect_is(dl, "raw") - - -} else -{ - message("To run tests, add a file ~/.azureml/settings.json containing AzureML keys, see ?workspace for help") - message("No tests ran") -} +}) diff --git a/tests/testthat/test-5-publish.R b/tests/testthat/test-5-publish.R index e3a0d15..b78eb37 100644 --- a/tests/testthat/test-5-publish.R +++ b/tests/testthat/test-5-publish.R @@ -1,12 +1,16 @@ if(interactive()) library(testthat) context("Publish API") -ws <- workspace() -endpoint <- NA - -test_that(".getexports finds function and creates zip string", { +settingsFile <- AzureML.config.default +test_that(".getexports finds function and creates zip string", { + AzureML:::skip_if_missing_config(settingsFile) + + ws <<- workspace() + endpoint <<- NA + + funEnv <- new.env() assign("add", function(x, y) x + y, envir = funEnv) @@ -31,6 +35,7 @@ test_that(".getexports finds function and creates zip string", { test_that("publishWebService throws error if fun is not a function", { + AzureML:::skip_if_missing_config(settingsFile) add <- function(x,y) x + y timestamped_name <- paste0("webservice-test-publish-", @@ -56,6 +61,7 @@ timestamped_name <- paste0("webservice-test-publish-", test_that("publishWebService works with simple function", { + AzureML:::skip_if_missing_config(settingsFile) add <- function(x,y) x + y endpoint <- publishWebService(ws, @@ -83,6 +89,7 @@ test_that("publishWebService works with simple function", { test_that("updateWebService works with simple function", { # Now test updateWebService + AzureML:::skip_if_missing_config(settingsFile) endpoint <- updateWebService(ws, serviceId = endpoint$WebServiceId, fun = function(x, y) x - y, @@ -104,10 +111,12 @@ test_that("updateWebService works with simple function", { test_that("publishWebService works with data frame input", { + AzureML:::skip_if_missing_config(settingsFile) timestamped_name <- paste0("webservice-test-publish-", format(Sys.time(), format="%Y-%m-%d--%H-%M-%S")) + + if(!require("lme4")) skip("You need to install lme4 to run this test") - library(lme4) set.seed(1) train <- sleepstudy[sample(nrow(sleepstudy), 120),] m <- lm(Reaction ~ Days + Subject, data = train) @@ -135,6 +144,7 @@ test_that("publishWebService works with data frame input", { deleteWebService(ws, timestamped_name) }) + test_that("try_fetch gives exponential retry messages",{ set.seed(1) with_mock(