Skip to content

Commit

Permalink
Clean split usage in tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
Sun Rui committed Apr 24, 2015
1 parent d531c86 commit 046bc9e
Showing 1 changed file with 6 additions and 6 deletions.
12 changes: 6 additions & 6 deletions R/pkg/inst/tests/test_rdd.R
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,8 @@ test_that("several transformations on RDD (a benchmark on PipelinedRDD)", {
rdd2 <- rdd
for (i in 1:12)
rdd2 <- lapplyPartitionsWithIndex(
rdd2, function(split, part) {
part <- as.list(unlist(part) * split + i)
rdd2, function(partIndex, part) {
part <- as.list(unlist(part) * partIndex + i)
})
rdd2 <- lapply(rdd2, function(x) x + x)
actual <- collect(rdd2)
Expand All @@ -121,8 +121,8 @@ test_that("PipelinedRDD support actions: cache(), persist(), unpersist(), checkp
# PipelinedRDD
rdd2 <- lapplyPartitionsWithIndex(
rdd2,
function(split, part) {
part <- as.list(unlist(part) * split)
function(partIndex, part) {
part <- as.list(unlist(part) * partIndex)
})

cache(rdd2)
Expand Down Expand Up @@ -174,13 +174,13 @@ test_that("lapply with dependency", {
})

test_that("lapplyPartitionsWithIndex on RDDs", {
func <- function(splitIndex, part) { list(splitIndex, Reduce("+", part)) }
func <- function(partIndex, part) { list(partIndex, Reduce("+", part)) }
actual <- collect(lapplyPartitionsWithIndex(rdd, func), flatten = FALSE)
expect_equal(actual, list(list(0, 15), list(1, 40)))

pairsRDD <- parallelize(sc, list(list(1, 2), list(3, 4), list(4, 8)), 1L)
partitionByParity <- function(key) { if (key %% 2 == 1) 0 else 1 }
mkTup <- function(splitIndex, part) { list(splitIndex, part) }
mkTup <- function(partIndex, part) { list(partIndex, part) }
actual <- collect(lapplyPartitionsWithIndex(
partitionBy(pairsRDD, 2L, partitionByParity),
mkTup),
Expand Down

0 comments on commit 046bc9e

Please sign in to comment.