Skip to content

Commit

Permalink
Add "step" parameter to mlflow_log_metric in R (mlflow#1237)
Browse files Browse the repository at this point in the history
* Initial progress

* Add tests and default behavior for step with docs

* Test fix

* Docs phrasing

* Fix tests
  • Loading branch information
dbczumar committed May 10, 2019
1 parent 68478dd commit 9780aeb
Show file tree
Hide file tree
Showing 2 changed files with 108 additions and 5 deletions.
16 changes: 11 additions & 5 deletions mlflow/R/mlflow/R/tracking-runs.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,26 +2,32 @@
#'
#' Logs a metric for a run. Metrics key-value pair that records a single float measure.
#' During a single execution of a run, a particular metric can be logged several times.
#' Backend will keep track of historical values along with timestamps.
#' The MLflow Backend keeps track of historical metric values along two axes: timestamp and step.
#'
#' @param key Name of the metric.
#' @param value Float value for the metric being logged.
#' @param timestamp Unix timestamp in milliseconds at the time metric was logged.
#' @param timestamp Timestamp at which to log the metric. Timestamp is rounded to the nearest
#' integer. If unspecified, the number of milliseconds since the Unix epoch is used.
#' @param step Step at which to log the metric. Step is rounded to the nearest integer. If
#' unspecified, the default value of zero is used.
#' @template roxlate-run-id
#' @template roxlate-client
#' @export
mlflow_log_metric <- function(key, value, timestamp = NULL, run_id = NULL, client = NULL) {
mlflow_log_metric <- function(key, value, timestamp = NULL, step = NULL, run_id = NULL,
client = NULL) {
c(client, run_id) %<-% resolve_client_and_run_id(client, run_id)
key <- cast_string(key)
value <- cast_scalar_double(value)
timestamp <- cast_nullable_scalar_double(timestamp)
timestamp <- timestamp %||% current_time()
timestamp <- round(timestamp %||% current_time())
step <- round(cast_nullable_scalar_double(step) %||% 0)
mlflow_rest("runs", "log-metric", client = client, verb = "POST", data = list(
run_uuid = run_id,
run_id = run_id,
key = key,
value = value,
timestamp = timestamp
timestamp = timestamp,
step = step
))
invisible(value)
}
Expand Down
97 changes: 97 additions & 0 deletions mlflow/R/mlflow/tests/testthat/test-tracking-runs.R
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ test_that("logging functionality", {
metric_history <- mlflow_get_metric_history("mse", ended_run$run_uuid)
expect_identical(metric_history$key, c("mse", "mse"))
expect_identical(metric_history$value, c(24, 25))
expect_identical(metric_history$step, c(0, 0))
expect_true(all(difftime(metric_history$timestamp, run_start_time) >= 0))
expect_true(all(difftime(metric_history$timestamp, run_end_time) <= 0))

Expand All @@ -79,6 +80,102 @@ test_that("logging functionality", {
)
})

test_that("mlflow_log_metric() rounds step and timestamp inputs", {
mlflow_clear_test_dir("mlruns")
mlflow_start_run()

step_inputs <- runif(10, min = -20, max = 100)
for (step_input in step_inputs) {
mlflow_log_metric(key = "step_metric",
value = runif(1),
step = step_input,
timestamp = 100)
}
expect_setequal(
mlflow_get_metric_history("step_metric")$step,
round(step_inputs)
)

timestamp_inputs <- runif(10, 1000, 100000)
for (timestamp_input in timestamp_inputs) {
mlflow_log_metric(key = "timestamp_metric",
value = runif(1),
step = 0,
timestamp = timestamp_input)
}
expect_setequal(
mlflow_get_metric_history("timestamp_metric")$timestamp,
purrr::map(round(timestamp_inputs), mlflow:::milliseconds_to_date)
)
})

test_that("mlflow_log_metric() with step produces expected metric data", {
mlflow_clear_test_dir("mlruns")
mlflow_start_run()

metric_key_1 <- "test_metric_1"
mlflow_log_metric(key = metric_key_1,
value = 1.2,
step = -2,
timestamp = 300)
mlflow_log_metric(key = metric_key_1,
value = 137.4,
timestamp = 100)
mlflow_log_metric(key = metric_key_1,
value = -20,
timestamp = 200)

metric_key_2 <- "test_metric_2"
mlflow_log_metric(key = metric_key_2,
value = 14,
step = 120)
mlflow_log_metric(key = metric_key_2,
value = 56,
step = 137)
mlflow_log_metric(key = metric_key_2,
value = 20,
step = -5)

run <- mlflow_get_run()
metrics <- run$metrics[[1]]
expect_setequal(
metrics$key,
c("test_metric_1", "test_metric_2")
)
expect_setequal(
metrics$value,
c(-20, 56)
)
expect_setequal(
metrics$step,
c(0, 137)
)

metric_history_1 <- mlflow_get_metric_history("test_metric_1")
expect_setequal(
metric_history_1$value,
c(1.2, 137.4, -20)
)
expect_setequal(
metric_history_1$timestamp,
purrr::map(c(300, 100, 200), mlflow:::milliseconds_to_date)
)
expect_setequal(
metric_history_1$step,
c(-2, 0, 0)
)

metric_history_2 <- mlflow_get_metric_history("test_metric_2")
expect_setequal(
metric_history_2$value,
c(14, 56, 20)
)
expect_setequal(
metric_history_2$step,
c(120, 137, -5)
)
})

test_that("mlflow_end_run() behavior", {
mlflow_clear_test_dir("mlruns")
expect_error(
Expand Down

0 comments on commit 9780aeb

Please sign in to comment.