From 24ea885122cc0d7808665dc1f9186db0197f1182 Mon Sep 17 00:00:00 2001 From: wlandau Date: Fri, 8 Nov 2024 12:48:34 -0500 Subject: [PATCH 01/23] rename method --- R/class_junction.R | 2 +- R/class_pattern.R | 2 +- R/class_stem.R | 2 +- tests/testthat/test-class_junction.R | 6 +++--- 4 files changed, 6 insertions(+), 6 deletions(-) diff --git a/R/class_junction.R b/R/class_junction.R index 34867e68..d615604a 100644 --- a/R/class_junction.R +++ b/R/class_junction.R @@ -23,7 +23,7 @@ junction_upstream_edges <- function(junction) { data_frame(from = from, to = to) } -junction_get_splits <- function(junction) { +junction_splits <- function(junction) { as.character(junction$splits) } diff --git a/R/class_pattern.R b/R/class_pattern.R index bd3e4ad8..5099e816 100644 --- a/R/class_pattern.R +++ b/R/class_pattern.R @@ -44,7 +44,7 @@ pattern_s3_class <- c("tar_pattern", "tar_target") #' @export target_get_children.tar_pattern <- function(target) { - junction_get_splits(target$junction) + junction_splits(target$junction) } #' @export diff --git a/R/class_stem.R b/R/class_stem.R index f28023af..a9109013 100644 --- a/R/class_stem.R +++ b/R/class_stem.R @@ -47,7 +47,7 @@ target_get_children.tar_stem <- function(target) { if_any( is.null(target$junction), character(0), - junction_get_splits(target$junction) + junction_splits(target$junction) ) } diff --git a/tests/testthat/test-class_junction.R b/tests/testthat/test-class_junction.R index 8f35e46b..b7d6699a 100644 --- a/tests/testthat/test-class_junction.R +++ b/tests/testthat/test-class_junction.R @@ -5,15 +5,15 @@ tar_test("junction deps", { expect_equal(out, exp) }) -tar_test("junction_get_splits()", { +tar_test("junction_splits()", { x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) - expect_equal(junction_get_splits(x), letters) + expect_equal(junction_splits(x), letters) }) tar_test("junction_invalidate()", { x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) junction_invalidate(x) - expect_equal(junction_get_splits(x), rep(NA_character_, length(x$splits))) + expect_equal(junction_splits(x), rep(NA_character_, length(x$splits))) }) tar_test("junction_upstream_edges()", { From 32e9d0d8420a038e8dfe2a8d9217051f8988ad91 Mon Sep 17 00:00:00 2001 From: wlandau Date: Fri, 8 Nov 2024 12:54:33 -0500 Subject: [PATCH 02/23] refactor jucntion --- R/class_junction.R | 20 +++++++++++--------- tests/testthat/test-class_junction.R | 2 +- tests/testthat/test-class_stem.R | 2 +- 3 files changed, 13 insertions(+), 11 deletions(-) diff --git a/R/class_junction.R b/R/class_junction.R index d615604a..1d8f5f4f 100644 --- a/R/class_junction.R +++ b/R/class_junction.R @@ -3,32 +3,33 @@ junction_init <- function( splits = character(0), deps = list() ) { - splits <- make.unique(splits, sep = "_") + index <- seq_along(splits) + names(index) <- make.unique(splits, sep = "_") names(deps) <- names(deps) %|||% seq_along(deps) deps <- as_data_frame(deps) - junction_new(nexus, splits, deps) + junction_new(nexus, index, deps) } -junction_new <- function(nexus = NULL, splits = NULL, deps = NULL) { +junction_new <- function(nexus = NULL, index = NULL, deps = NULL) { out <- new.env(parent = emptyenv(), hash = FALSE) out$nexus <- nexus - out$splits <- splits + out$index <- index out$deps <- deps out } junction_upstream_edges <- function(junction) { from <- utils::stack(junction$deps)$values - to <- rep(junction$splits, times = ncol(junction$deps)) + to <- rep(junction_splits(junction), times = ncol(junction$deps)) data_frame(from = from, to = to) } junction_splits <- function(junction) { - as.character(junction$splits) + names(junction$index) } junction_transpose <- function(junction) { - splits <- junction$splits + splits <- junction_splits(junction) deps <- junction$deps out <- map_rows(deps, ~list(deps = unname(.x))) %||% replicate(length(splits), list(deps = character(0)), simplify = FALSE) @@ -39,7 +40,7 @@ junction_transpose <- function(junction) { } junction_invalidate <- function(junction) { - junction$splits <- rep(NA_character_, length(junction$splits)) + names(junction$index) <- rep(NA_character_, length(junction$index)) } junction_validate_deps <- function(deps) { @@ -52,6 +53,7 @@ junction_validate <- function(junction) { tar_assert_correct_fields(junction, junction_new) tar_assert_scalar(junction$nexus) tar_assert_chr(junction$nexus) - tar_assert_chr(junction$splits) + tar_assert_int(junction$index) + tar_assert_chr(junction_splits(junction)) junction_validate_deps(junction$deps) } diff --git a/tests/testthat/test-class_junction.R b/tests/testthat/test-class_junction.R index b7d6699a..2ffbf40b 100644 --- a/tests/testthat/test-class_junction.R +++ b/tests/testthat/test-class_junction.R @@ -13,7 +13,7 @@ tar_test("junction_splits()", { tar_test("junction_invalidate()", { x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) junction_invalidate(x) - expect_equal(junction_splits(x), rep(NA_character_, length(x$splits))) + expect_equal(junction_splits(x), rep(NA_character_, length(x$index))) }) tar_test("junction_upstream_edges()", { diff --git a/tests/testthat/test-class_stem.R b/tests/testthat/test-class_stem.R index 5d2afbe8..9b3b0282 100644 --- a/tests/testthat/test-class_stem.R +++ b/tests/testthat/test-class_stem.R @@ -24,7 +24,7 @@ tar_test("stem$update_junction() on a good stem", { pipeline <- pipeline_init(list(x)) stem_update_junction(x, pipeline) expect_silent(junction_validate(x$junction)) - out <- x$junction$splits + out <- junction_splits(x$junction) expect_length(out, 10L) expect_true(all(grepl("abc_", out))) }) From 19f4a7d13ad409ce913de2230d762a846f12c38f Mon Sep 17 00:00:00 2001 From: wlandau Date: Fri, 8 Nov 2024 13:59:35 -0500 Subject: [PATCH 03/23] eliminate junction_transpose() --- R/class_junction.R | 40 ++++++++++++++-------- R/class_pattern.R | 39 +++++++++++---------- tests/testthat/test-class_junction.R | 51 +++++++++++++--------------- 3 files changed, 69 insertions(+), 61 deletions(-) diff --git a/R/class_junction.R b/R/class_junction.R index 1d8f5f4f..f7fcffef 100644 --- a/R/class_junction.R +++ b/R/class_junction.R @@ -3,40 +3,52 @@ junction_init <- function( splits = character(0), deps = list() ) { + splits <- make.unique(splits, sep = "_") index <- seq_along(splits) - names(index) <- make.unique(splits, sep = "_") - names(deps) <- names(deps) %|||% seq_along(deps) + names(index) <- splits deps <- as_data_frame(deps) - junction_new(nexus, index, deps) + has_deps <- nrow(deps) > 0L + junction_new(nexus, index, deps, has_deps) } -junction_new <- function(nexus = NULL, index = NULL, deps = NULL) { +junction_new <- function( + nexus = NULL, + index = NULL, + deps = NULL, + has_deps = NULL +) { out <- new.env(parent = emptyenv(), hash = FALSE) out$nexus <- nexus out$index <- index out$deps <- deps + out$has_deps <- has_deps out } junction_upstream_edges <- function(junction) { - from <- utils::stack(junction$deps)$values + from <- unlist(junction$deps, use.names = FALSE) to <- rep(junction_splits(junction), times = ncol(junction$deps)) data_frame(from = from, to = to) } +junction_length <- function(junction) { + length(.subset2(junction, "index")) +} + junction_splits <- function(junction) { - names(junction$index) + names(.subset2(junction, "index")) } -junction_transpose <- function(junction) { - splits <- junction_splits(junction) - deps <- junction$deps - out <- map_rows(deps, ~list(deps = unname(.x))) %||% - replicate(length(splits), list(deps = character(0)), simplify = FALSE) - for (index in seq_along(splits)) { - out[[index]]$split <- splits[index] +junction_extract_index <- function(junction, name) { + as.integer(.subset2(.subset2(junction, "index"), name)) +} + +junction_extract_deps <- function(junction, index) { + if (.subset2(junction, "has_deps")) { + as.character(vctrs::vec_slice(x = .subset2(junction, "deps"), i = index)) + } else { + character(0L) } - out } junction_invalidate <- function(junction) { diff --git a/R/class_pattern.R b/R/class_pattern.R index 5099e816..8b8db30b 100644 --- a/R/class_pattern.R +++ b/R/class_pattern.R @@ -247,27 +247,26 @@ pattern_prepend_branches <- function(target, scheduler) { scheduler$queue$prepend(children, ranks) } +pattern_produce_branch <- function(target, name) { + junction <- .subset2(target, "junction") + index <- junction_extract_index(junction, name) + branch_init( + name = name, + command = .subset2(target, "command"), + deps_parent = .subset2(target, "deps"), + deps_child = junction_extract_deps(junction, index), + settings = .subset2(target, "settings"), + cue = .subset2(target, "cue"), + store = .subset2(target, "store"), + index = index + ) +} + pattern_set_branches <- function(target, pipeline) { - command <- target$command - deps_parent <- target$deps - settings <- target$settings - cue <- target$cue - store <- target$store - specs <- junction_transpose(target$junction) - for (index in seq_along(specs)) { - spec <- .subset2(specs, index) - branch <- branch_init( - name = .subset2(spec, "split"), - command = command, - deps_parent = deps_parent, - deps_child = .subset2(spec, "deps"), - settings = settings, - cue = cue, - store = store, - index = index - ) - pipeline_set_target(pipeline, branch) - } + map( + junction_splits(target$junction), + ~pipeline_set_target(pipeline, pattern_produce_branch(target, .x)) + ) } pattern_insert_branches <- function(target, pipeline, scheduler) { diff --git a/tests/testthat/test-class_junction.R b/tests/testthat/test-class_junction.R index 2ffbf40b..f9c6ea66 100644 --- a/tests/testthat/test-class_junction.R +++ b/tests/testthat/test-class_junction.R @@ -1,8 +1,21 @@ -tar_test("junction deps", { +tar_test("junction with deps", { x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) out <- x$deps exp <- data_frame(a = LETTERS, b = rev(letters)) expect_equal(out, exp) + expect_true(x$has_deps) +}) + +tar_test("junction without deps", { + skip_cran() + x <- junction_init("x", letters, list()) + expect_equal(x$deps, data.frame()) + expect_false(x$has_deps) +}) + +tar_test("junction_length()", { + x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) + expect_equal(junction_length(x), length(letters)) }) tar_test("junction_splits()", { @@ -10,6 +23,16 @@ tar_test("junction_splits()", { expect_equal(junction_splits(x), letters) }) +tar_test("junction_extract_index()", { + x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) + expect_equal(junction_extract_index(x, "j"), 10L) +}) + +tar_test("junction_extract_deps()", { + x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) + expect_equal(junction_extract_deps(x, 10L), c("J", "q")) +}) + tar_test("junction_invalidate()", { x <- junction_init("x", letters, list(a = LETTERS, b = rev(letters))) junction_invalidate(x) @@ -26,32 +49,6 @@ tar_test("junction_upstream_edges()", { expect_equal(out, exp) }) -tar_test("junction_transpose() without deps", { - names <- paste0("child_", seq_len(3)) - junction <- junction_init("parent", names) - out <- junction_transpose(junction) - exp <- list(deps = character(0), split = "child_1") - expect_equal(out[[1]], exp) - exp <- list(deps = character(0), split = "child_2") - expect_equal(out[[2]], exp) - exp <- list(deps = character(0), split = "child_3") - expect_equal(out[[3]], exp) -}) - -tar_test("junction transpose() with deps", { - names <- paste0("child_", seq_len(3)) - x <- paste0("x_", seq_len(3)) - y <- paste0("y_", seq_len(3)) - junction <- junction_init("parent", names, list(x, y)) - out <- junction_transpose(junction) - exp <- list(deps = sort(c("x_1", "y_1")), split = "child_1") - expect_equal(out[[1]], exp) - exp <- list(deps = sort(c("x_2", "y_2")), split = "child_2") - expect_equal(out[[2]], exp) - exp <- list(deps = sort(c("x_3", "y_3")), split = "child_3") - expect_equal(out[[3]], exp) -}) - tar_test("junction_validate()", { x <- junction_init("x", letters, list(LETTERS, rev = rev(letters))) expect_silent(junction_validate(x)) From 975a7f0ed320c747917aae0e31999cf3e2376491 Mon Sep 17 00:00:00 2001 From: wlandau Date: Fri, 8 Nov 2024 14:11:09 -0500 Subject: [PATCH 04/23] produce buds differently --- R/class_stem.R | 13 ++++++++----- tests/testthat/test-class_stem.R | 4 ++-- 2 files changed, 10 insertions(+), 7 deletions(-) diff --git a/R/class_stem.R b/R/class_stem.R index a9109013..5083808e 100644 --- a/R/class_stem.R +++ b/R/class_stem.R @@ -166,14 +166,17 @@ stem_tar_assert_nonempty <- function(target) { } } -stem_produce_buds <- function(target) { - settings <- target$settings - names <- target_get_children(target) - map(seq_along(names), ~bud_new(names[.x], settings, .x)) +stem_produce_bud <- function(target, name) { + junction <- .subset2(target, "junction") + index <- junction_extract_index(junction, name) + bud_new(name = name, settings = .subset2(target, "settings"), index = index) } stem_insert_buds <- function(target, pipeline) { - map(stem_produce_buds(target), pipeline_set_target, pipeline = pipeline) + map( + junction_splits(target$junction), + ~pipeline_set_target(pipeline, stem_produce_bud(target, .x)) + ) } stem_ensure_buds <- function(target, pipeline, scheduler) { diff --git a/tests/testthat/test-class_stem.R b/tests/testthat/test-class_stem.R index 9b3b0282..cdce95d1 100644 --- a/tests/testthat/test-class_stem.R +++ b/tests/testthat/test-class_stem.R @@ -29,13 +29,13 @@ tar_test("stem$update_junction() on a good stem", { expect_true(all(grepl("abc_", out))) }) -tar_test("stem_produce_buds()", { +tar_test("stem produce buds", { x <- target_init(name = "abc", expr = quote(letters)) tar_option_set(envir = baseenv()) target_run(x, tar_option_get("envir"), path_store_default()) pipeline <- pipeline_init(list(x)) stem_update_junction(x, pipeline) - children <- stem_produce_buds(x) + children <- map(target_get_children(x), ~stem_produce_bud(x, .x)) expect_true(is.list(children)) expect_length(children, length(letters)) for (index in seq_along(letters)) { From 2c7c0c87b5fd2de2672a0e5bcf2cd80fe1116b02 Mon Sep 17 00:00:00 2001 From: wlandau Date: Fri, 8 Nov 2024 16:11:25 -0500 Subject: [PATCH 05/23] delegate pipeline_set_target() --- R/class_builder.R | 1 + R/class_clustermq.R | 1 - R/class_crew.R | 1 - R/class_future.R | 1 - R/class_pipeline.R | 16 ++++++++-------- 5 files changed, 9 insertions(+), 11 deletions(-) diff --git a/R/class_builder.R b/R/class_builder.R index 3b186373..a3b74abd 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -226,6 +226,7 @@ target_conclude.tar_builder <- function(target, pipeline, scheduler, meta) { builder_ensure_object(target, "main") builder_ensure_correct_hash(target) builder_handle_warnings(target, scheduler) + pipeline_set_target(pipeline, target) switch( metrics_outcome(target$metrics), cancel = builder_cancel(target, pipeline, scheduler, meta), diff --git a/R/class_clustermq.R b/R/class_clustermq.R index 0386a403..ae173485 100644 --- a/R/class_clustermq.R +++ b/R/class_clustermq.R @@ -209,7 +209,6 @@ clustermq_class <- R6::R6Class( if (is.null(target)) { return() } - pipeline_set_target(self$pipeline, target) self$unmarshal_target(target) target_conclude( target, diff --git a/R/class_crew.R b/R/class_crew.R index 39589b9b..4c4db331 100644 --- a/R/class_crew.R +++ b/R/class_crew.R @@ -236,7 +236,6 @@ crew_class <- R6::R6Class( msg = paste("target", result$name, "error:", result$error) ) target <- result$result[[1]] - pipeline_set_target(self$pipeline, target) self$unmarshal_target(target) target_conclude( target, diff --git a/R/class_future.R b/R/class_future.R index 46a2a179..3f60401e 100644 --- a/R/class_future.R +++ b/R/class_future.R @@ -169,7 +169,6 @@ future_class <- R6::R6Class( }, conclude_worker_target = function(value, name) { target <- future_value_target(value, name, self$pipeline) - pipeline_set_target(self$pipeline, target) self$unmarshal_target(target) target_conclude( target, diff --git a/R/class_pipeline.R b/R/class_pipeline.R index ea680bbe..cc1f7fea 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -44,6 +44,13 @@ pipeline_get_target <- function(pipeline, name) { .subset2(.subset2(pipeline, "targets"), name) } +pipeline_set_target <- function(pipeline, target) { + envir <- .subset2(pipeline, "targets") + name <- target_get_name(target) + envir[[name]] <- target + NULL +} + pipeline_get_names <- function(pipeline) { names(pipeline$targets) } @@ -78,13 +85,6 @@ pipeline_reset_deployment <- function(pipeline, name) { target$settings$deployment <- "main" } -pipeline_set_target <- function(pipeline, target) { - envir <- .subset2(pipeline, "targets") - name <- target_get_name(target) - envir[[name]] <- target - NULL -} - pipeline_exists_target <- function(pipeline, name) { envir <- pipeline$targets %|||% tar_empty_envir exists(x = name, envir = envir, inherits = FALSE) @@ -180,7 +180,7 @@ pipeline_produce_subpipeline <- function(pipeline, name, keep_value = NULL) { pipeline_assign_target_copy <- function(pipeline, name, envir, keep_value) { target <- pipeline_get_target(pipeline, name) copy <- target_subpipeline_copy(target, keep_value) - assign(name, copy, envir = envir) + envir[[name]] <- copy } pipeline_marshal_values <- function(pipeline) { From 1c5690337154d8b9a69a9016e69dc694215dc2af Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 08:32:17 -0500 Subject: [PATCH 06/23] condense target_read_value.tar_pattern() loop over branches --- R/class_pattern.R | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/R/class_pattern.R b/R/class_pattern.R index 8b8db30b..64f33df2 100644 --- a/R/class_pattern.R +++ b/R/class_pattern.R @@ -96,13 +96,13 @@ target_conclude.tar_pattern <- function(target, pipeline, scheduler, meta) { #' @export target_read_value.tar_pattern <- function(target, pipeline) { branches <- target_get_children(target) - map( - branches, - ~target_ensure_value(pipeline_get_target(pipeline, .x), pipeline) - ) objects <- map( branches, - ~pipeline_get_target(pipeline, .x)$value$object + ~ { + target <- pipeline_get_target(pipeline, .x) + target_ensure_value(target, pipeline) + target$value$object + } ) names(objects) <- branches value <- value_init(iteration = target$settings$iteration) From f0e082f01d5349b0011562aa87341b6c2a3c8692 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 08:46:49 -0500 Subject: [PATCH 07/23] set the target in the pipeline before every call to pipeline_register_loaded() --- R/class_builder.R | 3 ++- R/class_pipeline.R | 6 +----- R/class_target.R | 1 + tests/testthat/test-class_pipeline.R | 2 +- 4 files changed, 5 insertions(+), 7 deletions(-) diff --git a/R/class_builder.R b/R/class_builder.R index a3b74abd..5ae6feeb 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -226,7 +226,6 @@ target_conclude.tar_builder <- function(target, pipeline, scheduler, meta) { builder_ensure_object(target, "main") builder_ensure_correct_hash(target) builder_handle_warnings(target, scheduler) - pipeline_set_target(pipeline, target) switch( metrics_outcome(target$metrics), cancel = builder_cancel(target, pipeline, scheduler, meta), @@ -241,6 +240,7 @@ builder_completed <- function(target, pipeline, scheduler, meta) { target_ensure_buds(target, pipeline, scheduler) meta$insert_record(target_produce_record(target, pipeline, meta)) target_patternview_meta(target, pipeline, meta) + pipeline_set_target(pipeline, target) pipeline_register_loaded(pipeline, target_get_name(target)) scheduler$progress$register_completed(target) scheduler$reporter$report_completed(target, scheduler$progress) @@ -391,6 +391,7 @@ builder_error_null <- function(target, pipeline, scheduler, meta) { record$data <- "error" meta$insert_record(record) target_patternview_meta(target, pipeline, meta) + pipeline_set_target(pipeline, target) pipeline_register_loaded(pipeline, target_get_name(target)) scheduler$progress$register_errored(target) } diff --git a/R/class_pipeline.R b/R/class_pipeline.R index cc1f7fea..427154bf 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -123,7 +123,7 @@ pipeline_produce_igraph <- function(pipeline, targets_only = TRUE) { igraph::simplify(igraph::graph_from_data_frame(edges)) } -pipeline_register_loaded_target <- function(pipeline, name) { # nolint +pipeline_register_loaded <- function(pipeline, name) { # nolint counter_set_name(pipeline$loaded, name) target <- pipeline_get_target(pipeline, name) if (identical(target$settings$memory, "transient")) { @@ -131,10 +131,6 @@ pipeline_register_loaded_target <- function(pipeline, name) { # nolint } } -pipeline_register_loaded <- function(pipeline, names) { - lapply(names, pipeline_register_loaded_target, pipeline = pipeline) -} - pipeline_unload_target <- function(pipeline, name) { target <- pipeline_get_target(pipeline, name) store_unload(target$store, target) diff --git a/R/class_target.R b/R/class_target.R index 9b346a0a..e49ace0c 100644 --- a/R/class_target.R +++ b/R/class_target.R @@ -104,6 +104,7 @@ target_ensure_deps <- function(target, pipeline) { target_load_value <- function(target, pipeline) { target$value <- target_read_value(target, pipeline) + pipeline_set_target(pipeline, target) pipeline_register_loaded(pipeline, target_get_name(target)) } diff --git a/tests/testthat/test-class_pipeline.R b/tests/testthat/test-class_pipeline.R index fde8c0ed..28800e12 100644 --- a/tests/testthat/test-class_pipeline.R +++ b/tests/testthat/test-class_pipeline.R @@ -80,7 +80,7 @@ tar_test("pipeline_upstream_edges(targets_only = FALSE)", { expect_true(all(edges$to %in% names)) }) -tar_test("pipeline_register_loaded(pipeline, )", { +tar_test("pipeline_register_loaded()", { x <- target_init("x", quote(1), memory = "persistent") y <- target_init("y", quote(1), memory = "transient") pipeline <- pipeline_init(list(x, y)) From cbfdd2e0eb2725bc52a2370d68cba0a539992b09 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 09:01:35 -0500 Subject: [PATCH 08/23] move error handling to target_ensure_dep() --- R/class_builder.R | 15 +-------------- R/class_target.R | 17 ++++++++++++++++- 2 files changed, 17 insertions(+), 15 deletions(-) diff --git a/R/class_builder.R b/R/class_builder.R index 5ae6feeb..e24dae1c 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -307,20 +307,7 @@ builder_ensure_deps <- function(target, pipeline, retrieval) { if (!identical(target$settings$retrieval, retrieval)) { return() } - tryCatch( - target_ensure_deps(target, pipeline), - error = function(error) { - message <- paste0( - "could not load dependencies of target ", - target_get_name(target), - ". ", - conditionMessage(error) - ) - expr <- as.expression(as.call(list(quote(stop), message))) - target$command$expr <- expr - target$settings$deployment <- "main" - } - ) + target_ensure_deps(target, pipeline) } builder_update_subpipeline <- function(target, pipeline) { diff --git a/R/class_target.R b/R/class_target.R index e49ace0c..28561d6a 100644 --- a/R/class_target.R +++ b/R/class_target.R @@ -92,7 +92,22 @@ target_get_name <- function(target) { } target_ensure_dep <- function(target, dep, pipeline) { - target_ensure_value(dep, pipeline) + tryCatch( + target_ensure_value(dep, pipeline), + error = function(error) { + message <- paste0( + "could not load dependency ", + target_get_name(dep), + " of target ", + target_get_name(target), + ". ", + conditionMessage(error) + ) + expr <- as.expression(as.call(list(quote(stop), message))) + target$command$expr <- expr + target$settings$deployment <- "main" + } + ) } target_ensure_deps <- function(target, pipeline) { From 07e770a5518ef346ba3f9d294667a982c78a16cb Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 09:19:15 -0500 Subject: [PATCH 09/23] reduce calls to pipeline_get_target() when creating the subpipeline --- R/class_builder.R | 2 +- R/class_pipeline.R | 7 +++++-- R/class_workspace.R | 2 +- tests/testthat/test-class_pipeline.R | 6 +++++- 4 files changed, 12 insertions(+), 5 deletions(-) diff --git a/R/class_builder.R b/R/class_builder.R index e24dae1c..f705589f 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -313,7 +313,7 @@ builder_ensure_deps <- function(target, pipeline, retrieval) { builder_update_subpipeline <- function(target, pipeline) { target$subpipeline <- pipeline_produce_subpipeline( pipeline, - target_get_name(target) + target ) } diff --git a/R/class_pipeline.R b/R/class_pipeline.R index 427154bf..0171256e 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -154,8 +154,11 @@ pipeline_unload_transient <- function(pipeline) { } } -pipeline_produce_subpipeline <- function(pipeline, name, keep_value = NULL) { - target <- pipeline_get_target(pipeline, name) +pipeline_produce_subpipeline <- function( + pipeline, + target, + keep_value = NULL +) { deps <- target_deps_deep(target, pipeline) targets <- new.env(parent = emptyenv()) keep_value <- keep_value %|||% identical(target$settings$retrieval, "main") diff --git a/R/class_workspace.R b/R/class_workspace.R index 537790ed..dca77326 100644 --- a/R/class_workspace.R +++ b/R/class_workspace.R @@ -2,7 +2,7 @@ workspace_init <- function(target, pipeline) { target <- target_workspace_copy(target) subpipeline <- pipeline_produce_subpipeline( pipeline, - target_get_name(target), + target, keep_value = FALSE ) workspace_new(target = target, subpipeline = subpipeline) diff --git a/tests/testthat/test-class_pipeline.R b/tests/testthat/test-class_pipeline.R index 28800e12..1606856d 100644 --- a/tests/testthat/test-class_pipeline.R +++ b/tests/testthat/test-class_pipeline.R @@ -154,7 +154,11 @@ tar_test("pipeline_produce_subpipeline()", { ) local <- local_init(pipeline) local$run() - subpipeline <- pipeline_produce_subpipeline(pipeline, "summary") + target <- target_init( + name = "summary", + expr = quote(c(map, data0)) + ) + subpipeline <- pipeline_produce_subpipeline(pipeline, target) out <- sort(pipeline_get_names(subpipeline)) branches <- target_get_children(pipeline_get_target(pipeline, "map")) exp <- sort(c("data0", "map", branches)) From 0e38f183ff39ab6542826666e89788a9e8d8918c Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 09:46:20 -0500 Subject: [PATCH 10/23] make a class for a target reference --- R/class_reference.R | 15 +++++++++++++++ tests/testthat/test-class_reference.R | 26 ++++++++++++++++++++++++++ 2 files changed, 41 insertions(+) create mode 100644 R/class_reference.R create mode 100644 tests/testthat/test-class_reference.R diff --git a/R/class_reference.R b/R/class_reference.R new file mode 100644 index 00000000..eeafa135 --- /dev/null +++ b/R/class_reference.R @@ -0,0 +1,15 @@ +reference_new <- function(parent, path = NULL, stage = NULL) { + c(parent = parent, path = path, stage = stage) +} + +reference_parent <- function(reference) { + .subset(reference, "parent") +} + +reference_path <- function(reference) { + .subset(reference, "path") +} + +reference_stage <- function(reference) { + .subset2(reference, "stage") +} diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R new file mode 100644 index 00000000..9b7e935c --- /dev/null +++ b/tests/testthat/test-class_reference.R @@ -0,0 +1,26 @@ +tar_test("reference with only parent", { + out <- reference_new(parent = "my_parent") + expect_equal(out, c(parent = "my_parent")) +}) + +tar_test("reference with parent and path", { + out <- reference_new(parent = "my_parent", path = "my_path") + expect_equal(out, c(parent = "my_parent", path = "my_path")) +}) + +tar_test("reference with parent and stage", { + out <- reference_new(parent = "my_parent", stage = "my_stage") + expect_equal(out, c(parent = "my_parent", stage = "my_stage")) +}) + +tar_test("reference with parent and path", { + out <- reference_new( + parent = "my_parent", + path = "my_path", + stage = "my_stage" + ) + expect_equal( + out, + c(parent = "my_parent", path = "my_path", stage = "my_stage") + ) +}) From 23652fda9e433876409860408c1a07a225a21417 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 10:24:47 -0500 Subject: [PATCH 11/23] add methods to convert branches and buds to and from lightweight references --- NAMESPACE | 5 +++ R/class_branch.R | 10 +++++ R/class_bud.R | 5 +++ R/class_pattern.R | 5 +++ R/class_reference.R | 17 ++++++-- R/class_stem.R | 5 +++ R/class_target.R | 13 ++++++ tests/testthat/test-class_reference.R | 61 +++++++++++++++++++++++++++ 8 files changed, 118 insertions(+), 3 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index a10f4f71..c4d37f86 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -271,11 +271,16 @@ S3method(target_patternview_meta,default) S3method(target_patternview_meta,tar_branch) S3method(target_prepare,default) S3method(target_prepare,tar_builder) +S3method(target_produce_child,tar_pattern) +S3method(target_produce_child,tar_stem) S3method(target_produce_junction,tar_pattern) S3method(target_produce_junction,tar_stem) S3method(target_produce_record,tar_branch) S3method(target_produce_record,tar_pattern) S3method(target_produce_record,tar_stem) +S3method(target_produce_reference,default) +S3method(target_produce_reference,tar_branch) +S3method(target_produce_reference,tar_bud) S3method(target_read_value,tar_bud) S3method(target_read_value,tar_builder) S3method(target_read_value,tar_pattern) diff --git a/R/class_branch.R b/R/class_branch.R index a857211b..033f4259 100644 --- a/R/class_branch.R +++ b/R/class_branch.R @@ -143,3 +143,13 @@ target_patternview_errored.tar_branch <- function( parent <- pipeline_get_target(pipeline, target_get_parent(target)) patternview_register_errored(parent$patternview, parent, scheduler) } + +#' @export +target_produce_reference.tar_branch <- function(target) { + file <- .subset2(target, "file") + reference_new( + parent = target_get_parent(target), + path = .subset2(file, "path"), + stage = .subset2(file, "stage") + ) +} diff --git a/R/class_bud.R b/R/class_bud.R index c90a3667..5d3d23c4 100644 --- a/R/class_bud.R +++ b/R/class_bud.R @@ -21,6 +21,11 @@ target_read_value.tar_bud <- function(target, pipeline) { value_init(object, parent$settings$iteration) } +#' @export +target_produce_reference.tar_bud <- function(target) { + reference_new(parent = target_get_parent(target)) +} + #' @export target_validate.tar_bud <- function(target) { tar_assert_correct_fields(target, bud_new, optional = "value") diff --git a/R/class_pattern.R b/R/class_pattern.R index 64f33df2..71aa100b 100644 --- a/R/class_pattern.R +++ b/R/class_pattern.R @@ -204,6 +204,11 @@ target_unmarshal_value.tar_pattern <- function(target) { target$value <- NULL } +#' @export +target_produce_child.tar_pattern <- function(target, name) { + pattern_produce_branch(target, name) +} + #' @export print.tar_pattern <- function(x, ...) { cat( diff --git a/R/class_reference.R b/R/class_reference.R index eeafa135..f64524b2 100644 --- a/R/class_reference.R +++ b/R/class_reference.R @@ -3,13 +3,24 @@ reference_new <- function(parent, path = NULL, stage = NULL) { } reference_parent <- function(reference) { - .subset(reference, "parent") + as.character(.subset(reference, "parent")) } reference_path <- function(reference) { - .subset(reference, "path") + as.character(.subset(reference, "path")) } reference_stage <- function(reference) { - .subset2(reference, "stage") + as.character(.subset2(reference, "stage")) +} + +reference_produce_target <- function(reference, pipeline, name) { + parent <- pipeline_get_target(pipeline, reference_parent(reference)) + child <- target_produce_child(parent, name) + file <- .subset2(child, "file") + if (!is.null(file)) { + file$path <- reference_path(reference) + file$stage <- reference_stage(reference) + } + child } diff --git a/R/class_stem.R b/R/class_stem.R index 5083808e..88d7889c 100644 --- a/R/class_stem.R +++ b/R/class_stem.R @@ -217,6 +217,11 @@ stem_restore_junction <- function(target, pipeline, meta) { target$junction <- junction } +#' @export +target_produce_child.tar_stem <- function(target, name) { + stem_produce_bud(target, name) +} + #' @export print.tar_stem <- function(x, ...) { cat( diff --git a/R/class_target.R b/R/class_target.R index 28561d6a..114ce5b3 100644 --- a/R/class_target.R +++ b/R/class_target.R @@ -493,6 +493,19 @@ target_validate <- function(target) { UseMethod("target_validate") } +target_produce_child <- function(target, name) { + UseMethod("target_produce_child") +} + +target_produce_reference <- function(target) { + UseMethod("target_produce_reference") +} + +#' @export +target_produce_reference.default <- function(target) { + target +} + #' @export target_validate.tar_target <- function(target) { tar_assert_chr(target$name) diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index 9b7e935c..bace36bf 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -24,3 +24,64 @@ tar_test("reference with parent and path", { c(parent = "my_parent", path = "my_path", stage = "my_stage") ) }) + +tar_test("reference_produce_target() and its inverse", { + skip_cran() + pipeline <- pipeline_init( + list( + target_init( + name = "data", + expr = quote(seq_len(3L)) + ), + target_init( + name = "map", + expr = quote(data), + pattern = quote(map(data)) + ) + ) + ) + local <- local_init(pipeline) + local$run() + data <- pipeline_get_target(local$pipeline, "data") + map <- pipeline_get_target(local$pipeline, "map") + for (index in seq_len(3L)) { + bud_name <- junction_splits(data$junction)[index] + branch_name <- junction_splits(map$junction)[index] + bud <- pipeline_get_target(local$pipeline, bud_name) + branch <- pipeline_get_target(local$pipeline, branch_name) + expect_equal(target_produce_reference(data), data) + expect_equal(target_produce_reference(map), map) + bud_reference <- target_produce_reference(bud) + branch_reference <- target_produce_reference(branch) + expect_equal(bud_reference, c(parent = "data")) + expect_equal( + branch_reference, + c( + parent = "map", + path = branch$file$path, + stage = branch$file$stage + ) + ) + expect_equal(basename(dirname(branch$file$path)), "objects") + expect_equal(basename(dirname(branch$file$stage)), "scratch") + new_bud <- reference_produce_target(bud_reference, local$pipeline, bud_name) + rm(list = "value", envir = bud) + expect_equal(new_bud, bud) + new_branch <- reference_produce_target( + branch_reference, + local$pipeline, + branch_name + ) + rm(list = c("value", "metrics", "subpipeline"), envir = branch) + branch$file$hash <- NA_character_ + branch$file$size <- NA_character_ + branch$file$time <- NA_character_ + branch$file$bytes <- 0 + expect_equal(new_branch, branch) + pipeline_unload_loaded(pipeline) + target_load_value(bud, local$pipeline) + expect_equal(bud$value$object, index) + target_load_value(branch, local$pipeline) + expect_equal(branch$value$object, index) + } +}) From 1c7d48d103250911ec25494896e3f6bbd5e8a49c Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 10:53:39 -0500 Subject: [PATCH 12/23] convert buds and branches to lightweight references on unload --- R/class_pipeline.R | 20 +++++++-- R/class_reference.R | 2 + tests/testthat/test-class_pipeline.R | 60 +++++++++++++++++++++++++++ tests/testthat/test-class_reference.R | 4 +- 4 files changed, 82 insertions(+), 4 deletions(-) diff --git a/R/class_pipeline.R b/R/class_pipeline.R index 0171256e..81cfc50d 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -41,7 +41,11 @@ pipeline_targets_init <- function(targets, clone_targets) { } pipeline_get_target <- function(pipeline, name) { - .subset2(.subset2(pipeline, "targets"), name) + out <- .subset2(.subset2(pipeline, "targets"), name) + if (is_reference(out)) { + out <- reference_produce_target(out, pipeline, name) + } + out } pipeline_set_target <- function(pipeline, target) { @@ -51,6 +55,13 @@ pipeline_set_target <- function(pipeline, target) { NULL } +pipeline_set_reference <- function(pipeline, target) { + envir <- .subset2(pipeline, "targets") + name <- target_get_name(target) + envir[[name]] <- target_produce_reference(target) + NULL +} + pipeline_get_names <- function(pipeline) { names(pipeline$targets) } @@ -132,8 +143,11 @@ pipeline_register_loaded <- function(pipeline, name) { # nolint } pipeline_unload_target <- function(pipeline, name) { - target <- pipeline_get_target(pipeline, name) - store_unload(target$store, target) + target <- .subset2(.subset2(pipeline, "targets"), name) + if (!is_reference(target)) { + store_unload(target$store, target) + pipeline_set_reference(pipeline, target) + } counter_del_name(pipeline$loaded, name) counter_del_name(pipeline$transient, name) } diff --git a/R/class_reference.R b/R/class_reference.R index f64524b2..24f925f4 100644 --- a/R/class_reference.R +++ b/R/class_reference.R @@ -24,3 +24,5 @@ reference_produce_target <- function(reference, pipeline, name) { } child } + +is_reference <- is.character diff --git a/tests/testthat/test-class_pipeline.R b/tests/testthat/test-class_pipeline.R index 1606856d..f0a03f1f 100644 --- a/tests/testthat/test-class_pipeline.R +++ b/tests/testthat/test-class_pipeline.R @@ -281,3 +281,63 @@ tar_test("automatically ignore non-target objects", { expect_equal(nrow(out), 1L) expect_equal(out$name, "x") }) + +tar_test("managing lightweight references to targets in pipelines", { + skip_cran() + pipeline <- pipeline_init( + list( + target_init( + name = "data", + expr = quote(seq_len(3L)) + ), + target_init( + name = "map", + expr = quote(data), + pattern = quote(map(data)) + ) + ) + ) + local <- local_init(pipeline) + local$run() + data <- pipeline_get_target(local$pipeline, "data") + map <- pipeline_get_target(local$pipeline, "map") + for (index in seq_len(2L)) { + bud_name <- junction_splits(data$junction)[index] + branch_name <- junction_splits(map$junction)[index] + bud <- pipeline_get_target(local$pipeline, bud_name) + branch <- pipeline_get_target(local$pipeline, branch_name) + expect_equal( + pipeline$targets[[bud_name]], + c(parent = "data") + ) + expect_equal( + pipeline$targets[[branch_name]], + c( + parent = "map", + path = branch$file$path, + stage = branch$file$stage + ) + ) + expect_s3_class(bud, "tar_bud") + expect_s3_class(branch, "tar_branch") + target_load_value(bud, local$pipeline) + expect_equal(bud$value$object, index) + target_load_value(branch, local$pipeline) + expect_equal(branch$value$object, index) + expect_s3_class(local$pipeline$targets[[bud_name]], "tar_bud") + expect_s3_class(local$pipeline$targets[[branch_name]], "tar_branch") + pipeline_unload_loaded(local$pipeline) + expect_equal( + pipeline$targets[[bud_name]], + c(parent = "data") + ) + expect_equal( + pipeline$targets[[branch_name]], + c( + parent = "map", + path = branch$file$path, + stage = branch$file$stage + ) + ) + } +}) diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index bace36bf..fae3684d 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -72,7 +72,9 @@ tar_test("reference_produce_target() and its inverse", { local$pipeline, branch_name ) - rm(list = c("value", "metrics", "subpipeline"), envir = branch) + suppressWarnings( + rm(list = c("value", "metrics", "subpipeline"), envir = branch) + ) branch$file$hash <- NA_character_ branch$file$size <- NA_character_ branch$file$time <- NA_character_ From 2014a1a31e2de8714871c0cbe98a52c4cd2761f3 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 10:58:17 -0500 Subject: [PATCH 13/23] migrate a test --- tests/testthat/test-class_branch.R | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/testthat/test-class_branch.R b/tests/testthat/test-class_branch.R index 0d37f227..c9d816e7 100644 --- a/tests/testthat/test-class_branch.R +++ b/tests/testthat/test-class_branch.R @@ -140,6 +140,8 @@ tar_test("branch$produce_record() of a successful branch", { local$run() meta <- local$meta target <- pipeline_get_target(pipeline, target_get_children(map)[2L]) + target$file$hash <- hash_object(123L) + target$file$bytes <- 16 record <- target_produce_record(target, pipeline, meta) expect_silent(record_validate(record)) expect_true(grepl("^y_", record$name)) From 9c53941a06088005adecbbc52882d75290f65003 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 11:00:18 -0500 Subject: [PATCH 14/23] suppress a warning caused by a test --- tests/testthat/test-class_reference.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index fae3684d..2654e7ab 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -65,7 +65,7 @@ tar_test("reference_produce_target() and its inverse", { expect_equal(basename(dirname(branch$file$path)), "objects") expect_equal(basename(dirname(branch$file$stage)), "scratch") new_bud <- reference_produce_target(bud_reference, local$pipeline, bud_name) - rm(list = "value", envir = bud) + suppressWarnings(rm(list = "value", envir = bud)) expect_equal(new_bud, bud) new_branch <- reference_produce_target( branch_reference, From 83b706cdc1ff975e088fa7effd6c97f287e0433d Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 11:05:45 -0500 Subject: [PATCH 15/23] make references even lighter --- R/class_reference.R | 8 +++---- tests/testthat/test-class_pipeline.R | 22 ++++--------------- tests/testthat/test-class_reference.R | 31 +++++++++------------------ 3 files changed, 18 insertions(+), 43 deletions(-) diff --git a/R/class_reference.R b/R/class_reference.R index 24f925f4..9a3d221d 100644 --- a/R/class_reference.R +++ b/R/class_reference.R @@ -1,17 +1,17 @@ reference_new <- function(parent, path = NULL, stage = NULL) { - c(parent = parent, path = path, stage = stage) + c(parent, path, stage) } reference_parent <- function(reference) { - as.character(.subset(reference, "parent")) + .subset(reference, 1L) } reference_path <- function(reference) { - as.character(.subset(reference, "path")) + .subset(reference, 2L) } reference_stage <- function(reference) { - as.character(.subset2(reference, "stage")) + .subset2(reference, 3L) } reference_produce_target <- function(reference, pipeline, name) { diff --git a/tests/testthat/test-class_pipeline.R b/tests/testthat/test-class_pipeline.R index f0a03f1f..fe444117 100644 --- a/tests/testthat/test-class_pipeline.R +++ b/tests/testthat/test-class_pipeline.R @@ -306,17 +306,10 @@ tar_test("managing lightweight references to targets in pipelines", { branch_name <- junction_splits(map$junction)[index] bud <- pipeline_get_target(local$pipeline, bud_name) branch <- pipeline_get_target(local$pipeline, branch_name) - expect_equal( - pipeline$targets[[bud_name]], - c(parent = "data") - ) + expect_equal(pipeline$targets[[bud_name]], "data") expect_equal( pipeline$targets[[branch_name]], - c( - parent = "map", - path = branch$file$path, - stage = branch$file$stage - ) + c("map", branch$file$path, branch$file$stage) ) expect_s3_class(bud, "tar_bud") expect_s3_class(branch, "tar_branch") @@ -327,17 +320,10 @@ tar_test("managing lightweight references to targets in pipelines", { expect_s3_class(local$pipeline$targets[[bud_name]], "tar_bud") expect_s3_class(local$pipeline$targets[[branch_name]], "tar_branch") pipeline_unload_loaded(local$pipeline) - expect_equal( - pipeline$targets[[bud_name]], - c(parent = "data") - ) + expect_equal(pipeline$targets[[bud_name]], "data") expect_equal( pipeline$targets[[branch_name]], - c( - parent = "map", - path = branch$file$path, - stage = branch$file$stage - ) + c("map", branch$file$path, branch$file$stage) ) } }) diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index 2654e7ab..5945b5f7 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -1,27 +1,22 @@ tar_test("reference with only parent", { out <- reference_new(parent = "my_parent") - expect_equal(out, c(parent = "my_parent")) + expect_equal(out, c("my_parent")) }) -tar_test("reference with parent and path", { +tar_test("reference with parent and path but no stage", { out <- reference_new(parent = "my_parent", path = "my_path") - expect_equal(out, c(parent = "my_parent", path = "my_path")) -}) - -tar_test("reference with parent and stage", { - out <- reference_new(parent = "my_parent", stage = "my_stage") - expect_equal(out, c(parent = "my_parent", stage = "my_stage")) + expect_equal(out, c("my_parent", "my_path")) }) tar_test("reference with parent and path", { out <- reference_new( - parent = "my_parent", - path = "my_path", - stage = "my_stage" + "my_parent", + "my_path", + "my_stage" ) expect_equal( out, - c(parent = "my_parent", path = "my_path", stage = "my_stage") + c("my_parent", "my_path", "my_stage") ) }) @@ -29,9 +24,7 @@ tar_test("reference_produce_target() and its inverse", { skip_cran() pipeline <- pipeline_init( list( - target_init( - name = "data", - expr = quote(seq_len(3L)) + target_init(name = "data", expr = quote(seq_len(3L)) ), target_init( name = "map", @@ -53,14 +46,10 @@ tar_test("reference_produce_target() and its inverse", { expect_equal(target_produce_reference(map), map) bud_reference <- target_produce_reference(bud) branch_reference <- target_produce_reference(branch) - expect_equal(bud_reference, c(parent = "data")) + expect_equal(bud_reference, "data") expect_equal( branch_reference, - c( - parent = "map", - path = branch$file$path, - stage = branch$file$stage - ) + c("map", branch$file$path, branch$file$stage) ) expect_equal(basename(dirname(branch$file$path)), "objects") expect_equal(basename(dirname(branch$file$stage)), "scratch") From adef7ed79c281b583a1a241a73a3490a5237a91a Mon Sep 17 00:00:00 2001 From: wlandau Date: Sat, 9 Nov 2024 11:14:31 -0500 Subject: [PATCH 16/23] sketch initializing branches/buds as references --- R/class_pattern.R | 7 ++++--- R/class_pipeline.R | 12 ++++++++++++ R/class_stem.R | 7 ++++--- 3 files changed, 20 insertions(+), 6 deletions(-) diff --git a/R/class_pattern.R b/R/class_pattern.R index 71aa100b..8a0938c1 100644 --- a/R/class_pattern.R +++ b/R/class_pattern.R @@ -268,9 +268,10 @@ pattern_produce_branch <- function(target, name) { } pattern_set_branches <- function(target, pipeline) { - map( - junction_splits(target$junction), - ~pipeline_set_target(pipeline, pattern_produce_branch(target, .x)) + pipeline_initialize_references_children( + pipeline = pipeline, + name_parent = target_get_name(target), + names_children = junction_splits(target$junction) ) } diff --git a/R/class_pipeline.R b/R/class_pipeline.R index 81cfc50d..bc5c2231 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -62,6 +62,18 @@ pipeline_set_reference <- function(pipeline, target) { NULL } +pipeline_initialize_references_children <- function( + pipeline, + name_parent, + names_children +) { + envir <- .subset2(pipeline, "targets") + for (name in names_children) { + envir[[name]] <- name_parent + } + NULL +} + pipeline_get_names <- function(pipeline) { names(pipeline$targets) } diff --git a/R/class_stem.R b/R/class_stem.R index 88d7889c..d9aa3623 100644 --- a/R/class_stem.R +++ b/R/class_stem.R @@ -173,9 +173,10 @@ stem_produce_bud <- function(target, name) { } stem_insert_buds <- function(target, pipeline) { - map( - junction_splits(target$junction), - ~pipeline_set_target(pipeline, stem_produce_bud(target, .x)) + pipeline_initialize_references_children( + pipeline = pipeline, + name_parent = target_get_name(target), + names_children = junction_splits(target$junction) ) } From 81bcac04dd365e071e889f981eda7d985a3be965 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 04:38:58 -0500 Subject: [PATCH 17/23] avoid out of bounds indexing in references --- R/class_reference.R | 14 +++++++++++--- tests/testthat/test-class_reference.R | 13 +++++++++++-- 2 files changed, 22 insertions(+), 5 deletions(-) diff --git a/R/class_reference.R b/R/class_reference.R index 9a3d221d..b33c897b 100644 --- a/R/class_reference.R +++ b/R/class_reference.R @@ -3,15 +3,23 @@ reference_new <- function(parent, path = NULL, stage = NULL) { } reference_parent <- function(reference) { - .subset(reference, 1L) + reference[1L] } reference_path <- function(reference) { - .subset(reference, 2L) + if (length(reference) > 1L) { + reference[2L] + } else { + NA_character_ + } } reference_stage <- function(reference) { - .subset2(reference, 3L) + if (length(reference) > 2L) { + reference[3L] + } else { + NA_character_ + } } reference_produce_target <- function(reference, pipeline, name) { diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index 5945b5f7..4d36b841 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -1,14 +1,20 @@ tar_test("reference with only parent", { out <- reference_new(parent = "my_parent") - expect_equal(out, c("my_parent")) + expect_equal(out, "my_parent") + expect_equal(reference_parent(out), "my_parent") + expect_equal(reference_path(out), NA_character_) + expect_equal(reference_stage(out), NA_character_) }) tar_test("reference with parent and path but no stage", { out <- reference_new(parent = "my_parent", path = "my_path") expect_equal(out, c("my_parent", "my_path")) + expect_equal(reference_parent(out), "my_parent") + expect_equal(reference_path(out), "my_path") + expect_equal(reference_stage(out), NA_character_) }) -tar_test("reference with parent and path", { +tar_test("reference with parent, path, and stage", { out <- reference_new( "my_parent", "my_path", @@ -18,6 +24,9 @@ tar_test("reference with parent and path", { out, c("my_parent", "my_path", "my_stage") ) + expect_equal(reference_parent(out), "my_parent") + expect_equal(reference_path(out), "my_path") + expect_equal(reference_stage(out), "my_stage") }) tar_test("reference_produce_target() and its inverse", { From 484703c82432f48052ca320ad437424929d8428e Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 05:19:47 -0500 Subject: [PATCH 18/23] Fix a bug, need to fix more --- R/class_builder.R | 2 +- R/class_pipeline.R | 25 +++++++++++++++++++------ R/tar_described_as.R | 7 ++++++- 3 files changed, 26 insertions(+), 8 deletions(-) diff --git a/R/class_builder.R b/R/class_builder.R index f705589f..55339f68 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -332,7 +332,7 @@ builder_unmarshal_subpipeline <- function(target) { pipeline_unmarshal_values(target$subpipeline) } patterns <- fltr( - names(subpipeline$targets), + pipeline_get_names(subpipeline), ~inherits(pipeline_get_target(subpipeline, .x), "tar_pattern") ) map( diff --git a/R/class_pipeline.R b/R/class_pipeline.R index bc5c2231..059d7c52 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -75,7 +75,7 @@ pipeline_initialize_references_children <- function( } pipeline_get_names <- function(pipeline) { - names(pipeline$targets) + names(.subset2(pipeline, "targets")) } pipeline_get_priorities <- function(pipeline) { @@ -109,8 +109,11 @@ pipeline_reset_deployment <- function(pipeline, name) { } pipeline_exists_target <- function(pipeline, name) { - envir <- pipeline$targets %|||% tar_empty_envir - exists(x = name, envir = envir, inherits = FALSE) + envir <- .subset2(pipeline, "targets") + if (is.null(envir)) { + envir <- tar_empty_envir + } + !is.null(.subset2(envir, name)) } pipeline_exists_import <- function(pipeline, name) { @@ -127,7 +130,10 @@ pipeline_targets_only_edges <- function(edges) { } pipeline_upstream_edges <- function(pipeline, targets_only = TRUE) { - edge_list <- map(pipeline$targets, ~target_upstream_edges(.x)) + edge_list <- map( + pipeline_get_names(pipeline), + ~target_upstream_edges(pipeline_get_target(pipeline, .x)) + ) from <- map(edge_list, ~.x$from) to <- map(edge_list, ~.x$to) from <- unlist(from, recursive = FALSE, use.names = FALSE) @@ -233,7 +239,11 @@ pipeline_prune_targets <- function(pipeline, names) { graph <- pipeline_produce_igraph(pipeline, targets_only = TRUE) keep <- upstream_vertices(graph = graph, from = names) discard <- setdiff(pipeline_get_names(pipeline), keep) - remove(list = discard, envir = pipeline$targets, inherits = FALSE) + remove( + list = discard, + envir = .subset2(pipeline, "targets"), + inherits = FALSE + ) } pipeline_prune_shortcut <- function(pipeline, names, shortcut) { @@ -298,7 +308,10 @@ pipeline_validate_dag <- function(igraph) { } pipeline_validate_conflicts <- function(pipeline) { - conflicts <- intersect(names(pipeline$imports), names(pipeline$targets)) + conflicts <- intersect( + names(.subset2(pipeline, "imports")), + pipeline_get_names(pipeline) + ) msg <- paste0( "Targets and globals must have unique names. ", "Ignoring global objects that conflict with target names: ", diff --git a/R/tar_described_as.R b/R/tar_described_as.R index ef913913..c898b32d 100644 --- a/R/tar_described_as.R +++ b/R/tar_described_as.R @@ -79,7 +79,12 @@ tar_described_as_inner <- function( described_as_quosure, tidyselect ) { - descriptions <- unlist(map(pipeline$targets, ~.x$settings$description)) + descriptions <- unlist( + map( + pipeline_get_names(pipeline), + ~pipeline_get_target(pipeline, .x)$settings$description + ) + ) chosen <- tar_tidyselect_eval(described_as_quosure, unique(descriptions)) sort(unique(names(descriptions[descriptions %in% chosen]))) } From 58e29fbcfeb87a234e2e179c2f0d597d8ffa2767 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 05:26:33 -0500 Subject: [PATCH 19/23] fix tar_described_as() --- R/tar_described_as.R | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/R/tar_described_as.R b/R/tar_described_as.R index c898b32d..c2b0b4c2 100644 --- a/R/tar_described_as.R +++ b/R/tar_described_as.R @@ -79,12 +79,13 @@ tar_described_as_inner <- function( described_as_quosure, tidyselect ) { - descriptions <- unlist( - map( - pipeline_get_names(pipeline), - ~pipeline_get_target(pipeline, .x)$settings$description - ) + names <- pipeline_get_names(pipeline) + descriptions <- map( + names, + ~pipeline_get_target(pipeline, .x)$settings$description ) + names(descriptions) <- names + descriptions <- unlist(descriptions, use.names = TRUE) chosen <- tar_tidyselect_eval(described_as_quosure, unique(descriptions)) sort(unique(names(descriptions[descriptions %in% chosen]))) } From 2644e1a8d3b99293786400c340b1fa0b0d41028b Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 05:39:57 -0500 Subject: [PATCH 20/23] fix one test --- R/class_builder.R | 1 + 1 file changed, 1 insertion(+) diff --git a/R/class_builder.R b/R/class_builder.R index 55339f68..2938efed 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -42,6 +42,7 @@ target_bootstrap.tar_builder <- function( record <- target_bootstrap_record(target, meta) target$store <- record_bootstrap_store(record) target$file <- record_bootstrap_file(record) + pipeline_set_reference(pipeline, target) invisible() } From 4530c788ba396ce6c9f9fc0482504381bbf8017a Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 06:33:34 -0500 Subject: [PATCH 21/23] fix tests --- R/class_branch.R | 5 +-- R/class_bud.R | 2 +- R/class_builder.R | 3 +- R/class_pipeline.R | 2 +- R/class_reference.R | 37 +++++++++++++------- tests/testthat/test-class_pipeline.R | 30 ++++++++++------ tests/testthat/test-class_reference.R | 50 ++++++++++++++++----------- 7 files changed, 81 insertions(+), 48 deletions(-) diff --git a/R/class_branch.R b/R/class_branch.R index 033f4259..c4efdae0 100644 --- a/R/class_branch.R +++ b/R/class_branch.R @@ -147,9 +147,10 @@ target_patternview_errored.tar_branch <- function( #' @export target_produce_reference.tar_branch <- function(target) { file <- .subset2(target, "file") - reference_new( + reference_init( parent = target_get_parent(target), path = .subset2(file, "path"), - stage = .subset2(file, "stage") + stage = .subset2(file, "stage"), + hash = .subset2(file, "hash") ) } diff --git a/R/class_bud.R b/R/class_bud.R index 5d3d23c4..9cc79bdb 100644 --- a/R/class_bud.R +++ b/R/class_bud.R @@ -23,7 +23,7 @@ target_read_value.tar_bud <- function(target, pipeline) { #' @export target_produce_reference.tar_bud <- function(target) { - reference_new(parent = target_get_parent(target)) + reference_init(parent = target_get_parent(target)) } #' @export diff --git a/R/class_builder.R b/R/class_builder.R index 2938efed..ff47ea70 100644 --- a/R/class_builder.R +++ b/R/class_builder.R @@ -42,7 +42,7 @@ target_bootstrap.tar_builder <- function( record <- target_bootstrap_record(target, meta) target$store <- record_bootstrap_store(record) target$file <- record_bootstrap_file(record) - pipeline_set_reference(pipeline, target) + pipeline_set_target(pipeline, target) invisible() } @@ -192,6 +192,7 @@ target_skip.tar_builder <- function( ) { target_update_queue(target, scheduler) file_repopulate(target$file, meta$get_record(target_get_name(target))) + pipeline_set_target(pipeline, target) if (active) { builder_ensure_workspace( target = target, diff --git a/R/class_pipeline.R b/R/class_pipeline.R index 059d7c52..3abdba01 100644 --- a/R/class_pipeline.R +++ b/R/class_pipeline.R @@ -69,7 +69,7 @@ pipeline_initialize_references_children <- function( ) { envir <- .subset2(pipeline, "targets") for (name in names_children) { - envir[[name]] <- name_parent + envir[[name]] <- reference_init(parent = name_parent) } NULL } diff --git a/R/class_reference.R b/R/class_reference.R index b33c897b..0e91de1c 100644 --- a/R/class_reference.R +++ b/R/class_reference.R @@ -1,25 +1,35 @@ -reference_new <- function(parent, path = NULL, stage = NULL) { - c(parent, path, stage) +reference_init <- function( + parent = NA_character_, + path = NA_character_, + stage = NA_character_, + hash = NA_character_ +) { + reference_new(parent = parent, path = path, stage = stage, hash = hash) +} + +reference_new <- function( + parent = NULL, + path = NULL, + stage = NULL, + hash = NULL +) { + c(parent = parent, path = path, stage = stage, hash = hash) } reference_parent <- function(reference) { - reference[1L] + as.character(.subset(reference, 1L)) } reference_path <- function(reference) { - if (length(reference) > 1L) { - reference[2L] - } else { - NA_character_ - } + as.character(.subset(reference, 2L)) } reference_stage <- function(reference) { - if (length(reference) > 2L) { - reference[3L] - } else { - NA_character_ - } + as.character(.subset(reference, 3L)) +} + +reference_hash <- function(reference) { + as.character(.subset(reference, 4L)) } reference_produce_target <- function(reference, pipeline, name) { @@ -29,6 +39,7 @@ reference_produce_target <- function(reference, pipeline, name) { if (!is.null(file)) { file$path <- reference_path(reference) file$stage <- reference_stage(reference) + file$hash <- reference_hash(reference) } child } diff --git a/tests/testthat/test-class_pipeline.R b/tests/testthat/test-class_pipeline.R index fe444117..4ed46c25 100644 --- a/tests/testthat/test-class_pipeline.R +++ b/tests/testthat/test-class_pipeline.R @@ -306,11 +306,16 @@ tar_test("managing lightweight references to targets in pipelines", { branch_name <- junction_splits(map$junction)[index] bud <- pipeline_get_target(local$pipeline, bud_name) branch <- pipeline_get_target(local$pipeline, branch_name) - expect_equal(pipeline$targets[[bud_name]], "data") - expect_equal( - pipeline$targets[[branch_name]], - c("map", branch$file$path, branch$file$stage) - ) + reference <- pipeline$targets[[bud_name]] + expect_equal(reference_parent(reference), "data") + expect_equal(reference_path(reference), NA_character_) + expect_equal(reference_stage(reference), NA_character_) + expect_equal(reference_hash(reference), NA_character_) + reference <- pipeline$targets[[branch_name]] + expect_equal(reference_parent(reference), "map") + expect_equal(reference_path(reference), branch$file$path) + expect_equal(reference_stage(reference), branch$file$stage) + expect_equal(reference_hash(reference), branch$file$hash) expect_s3_class(bud, "tar_bud") expect_s3_class(branch, "tar_branch") target_load_value(bud, local$pipeline) @@ -320,10 +325,15 @@ tar_test("managing lightweight references to targets in pipelines", { expect_s3_class(local$pipeline$targets[[bud_name]], "tar_bud") expect_s3_class(local$pipeline$targets[[branch_name]], "tar_branch") pipeline_unload_loaded(local$pipeline) - expect_equal(pipeline$targets[[bud_name]], "data") - expect_equal( - pipeline$targets[[branch_name]], - c("map", branch$file$path, branch$file$stage) - ) + reference <- pipeline$targets[[bud_name]] + expect_equal(reference_parent(reference), "data") + expect_equal(reference_path(reference), NA_character_) + expect_equal(reference_stage(reference), NA_character_) + expect_equal(reference_hash(reference), NA_character_) + reference <- pipeline$targets[[branch_name]] + expect_equal(reference_parent(reference), "map") + expect_equal(reference_path(reference), branch$file$path) + expect_equal(reference_stage(reference), branch$file$stage) + expect_equal(reference_hash(reference), branch$file$hash) } }) diff --git a/tests/testthat/test-class_reference.R b/tests/testthat/test-class_reference.R index 4d36b841..82167052 100644 --- a/tests/testthat/test-class_reference.R +++ b/tests/testthat/test-class_reference.R @@ -1,32 +1,38 @@ tar_test("reference with only parent", { - out <- reference_new(parent = "my_parent") - expect_equal(out, "my_parent") + out <- reference_init(parent = "my_parent") expect_equal(reference_parent(out), "my_parent") expect_equal(reference_path(out), NA_character_) expect_equal(reference_stage(out), NA_character_) + expect_equal(reference_hash(out), NA_character_) }) -tar_test("reference with parent and path but no stage", { - out <- reference_new(parent = "my_parent", path = "my_path") - expect_equal(out, c("my_parent", "my_path")) +tar_test("reference with parent and path but no other fields", { + out <- reference_init(parent = "my_parent", path = "my_path") expect_equal(reference_parent(out), "my_parent") expect_equal(reference_path(out), "my_path") expect_equal(reference_stage(out), NA_character_) + expect_equal(reference_hash(out), NA_character_) }) -tar_test("reference with parent, path, and stage", { - out <- reference_new( - "my_parent", - "my_path", - "my_stage" - ) - expect_equal( - out, - c("my_parent", "my_path", "my_stage") +tar_test("reference with parent and hash but no other fields", { + out <- reference_init(parent = "my_parent", hash = "my_hash") + expect_equal(reference_parent(out), "my_parent") + expect_equal(reference_path(out), NA_character_) + expect_equal(reference_stage(out), NA_character_) + expect_equal(reference_hash(out), "my_hash") +}) + +tar_test("reference with all fields", { + out <- reference_init( + parent = "my_parent", + path = "my_path", + stage = "my_stage", + hash = "my_hash" ) expect_equal(reference_parent(out), "my_parent") expect_equal(reference_path(out), "my_path") expect_equal(reference_stage(out), "my_stage") + expect_equal(reference_hash(out), "my_hash") }) tar_test("reference_produce_target() and its inverse", { @@ -55,13 +61,18 @@ tar_test("reference_produce_target() and its inverse", { expect_equal(target_produce_reference(map), map) bud_reference <- target_produce_reference(bud) branch_reference <- target_produce_reference(branch) - expect_equal(bud_reference, "data") - expect_equal( - branch_reference, - c("map", branch$file$path, branch$file$stage) - ) + expect_equal(reference_parent(bud_reference), "data") + expect_equal(reference_path(bud_reference), NA_character_) + expect_equal(reference_stage(bud_reference), NA_character_) + expect_equal(reference_hash(bud_reference), NA_character_) + expect_equal(reference_parent(branch_reference), "map") + expect_equal(reference_path(branch_reference), branch$file$path) + expect_equal(reference_stage(branch_reference), branch$file$stage) + expect_equal(reference_hash(branch_reference), branch$file$hash) expect_equal(basename(dirname(branch$file$path)), "objects") expect_equal(basename(dirname(branch$file$stage)), "scratch") + expect_false(anyNA(branch$file$hash)) + expect_equal(nchar(branch$file$hash), 16L) new_bud <- reference_produce_target(bud_reference, local$pipeline, bud_name) suppressWarnings(rm(list = "value", envir = bud)) expect_equal(new_bud, bud) @@ -73,7 +84,6 @@ tar_test("reference_produce_target() and its inverse", { suppressWarnings( rm(list = c("value", "metrics", "subpipeline"), envir = branch) ) - branch$file$hash <- NA_character_ branch$file$size <- NA_character_ branch$file$time <- NA_character_ branch$file$bytes <- 0 From 9782dc08125a53d839baf9886edf2c617e079b6f Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 06:38:43 -0500 Subject: [PATCH 22/23] fix tests --- .../testthat/test-tar_repository_cas_local.R | 52 +++++++++++++++++++ 1 file changed, 52 insertions(+) diff --git a/tests/testthat/test-tar_repository_cas_local.R b/tests/testthat/test-tar_repository_cas_local.R index d94d63b9..fb922e2a 100644 --- a/tests/testthat/test-tar_repository_cas_local.R +++ b/tests/testthat/test-tar_repository_cas_local.R @@ -98,3 +98,55 @@ tar_test("local CAS repository works on custom directory", { expect_equal(tar_outdated(), "z") tar_destroy() }) + +tar_test("local CAS repository with some invalidated branches", { + skip_cran() + tar_script({ + tar_option_set(repository = tar_repository_cas_local(path = "cas")) + tar_option_set(memory = "transient") + list( + tar_target(x, seq_len(3)), + tar_target(y, x, pattern = map(x)), + tar_target(z, y, pattern = map(y)), + tar_target(w, sum(y)) + ) + }) + tar_make(callr_function = NULL) + tar_script({ + tar_option_set(repository = tar_repository_cas_local(path = "cas")) + tar_option_set(memory = "transient") + list( + tar_target(x, c(1L, 5L, 3L)), + tar_target(y, x, pattern = map(x)), + tar_target(z, y, pattern = map(y)), + tar_target(w, sum(y)) + ) + }) + tar_make(callr_function = NULL) + expect_equal(tar_read(w), 9L) +}) + +tar_test("local CAS repository while depending on all branches", { + skip_cran() + tar_script({ + tar_option_set(repository = tar_repository_cas_local(path = "cas")) + tar_option_set(memory = "transient") + list( + tar_target(x, seq_len(3)), + tar_target(y, x, pattern = map(x)), + tar_target(z, y) + ) + }) + tar_make(callr_function = NULL) + tar_script({ + tar_option_set(repository = tar_repository_cas_local(path = "cas")) + tar_option_set(memory = "transient") + list( + tar_target(x, c(1L, 5L, 3L)), + tar_target(y, x, pattern = map(x)), + tar_target(z, y) + ) + }) + tar_make(callr_function = NULL) + expect_equal(as.integer(tar_read(z)), c(1L, 5L, 3L)) +}) From 49a6697147faa237e333271c165db256f87b5a67 Mon Sep 17 00:00:00 2001 From: wlandau Date: Sun, 10 Nov 2024 07:12:33 -0500 Subject: [PATCH 23/23] version and news --- DESCRIPTION | 2 +- NEWS.md | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 75eb19ad..ecd5f072 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -12,7 +12,7 @@ Description: Pipeline tools coordinate the pieces of computationally The methodology in this package borrows from GNU 'Make' (2015, ISBN:978-9881443519) and 'drake' (2018, ). -Version: 1.8.0.9009 +Version: 1.8.0.9010 License: MIT + file LICENSE URL: https://docs.ropensci.org/targets/, https://github.com/ropensci/targets BugReports: https://github.com/ropensci/targets/issues diff --git a/NEWS.md b/NEWS.md index 4c4ae7ed..f01d9288 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# targets 1.8.0.9009 (development) +# targets 1.8.0.9010 (development) * Un-break workflows that use `format = "file_fast"` (#1339, @koefoeden). * Fix deadlock in `error = "trim"` (#1340, @koefoeden). @@ -12,6 +12,7 @@ * Avoid `store_assert_format()` and `store_convert_object()` is `storage` is `"none"`. * Add a `list()` method to `tar_repository_cas()` to make it easier and more efficient to specify custom CAS repositories (#1366). * Improve speed and reduce memory consumption by avoiding deep copies of inner environments of target definition objects (#1368). +* Reduce memory consumption by storing buds and branches as lightweight references when `memory` is `"transient"` (#1364). # targets 1.8.0