Skip to content

Commit

Permalink
Update FlashR wrapper.
Browse files Browse the repository at this point in the history
  • Loading branch information
zheng-da committed Jan 20, 2017
1 parent 09e9004 commit 0e61857
Show file tree
Hide file tree
Showing 4 changed files with 89 additions and 2 deletions.
2 changes: 1 addition & 1 deletion R/FlashR.R
Original file line number Diff line number Diff line change
Expand Up @@ -2019,7 +2019,7 @@ fm.rbind.list <- function(objs)
return(objs[[1]])
}
for (fm in objs) {
if (fm.is.object(fm)) {
if (!fm.is.object(fm)) {
print("fm.rbind only works on FlashR matrix")
return(NULL)
}
Expand Down
64 changes: 64 additions & 0 deletions inst/tests/test_core.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,70 @@ test_that("load a dense matrix from a text file", {
# TODO I also need to test when the input text file has missing values.
})

test_that("load a sparse matrix from a text file", {
download.file("http://snap.stanford.edu/data/wiki-Vote.txt.gz", "wiki-Vote.txt.gz")
system("gunzip wiki-Vote.txt.gz")
mat <- fm.load.sparse.matrix("wiki-Vote.txt", in.mem=TRUE, is.sym=FALSE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 8298)
expect_equal(sum(res), 103689)

mat <- fm.load.sparse.matrix("wiki-Vote.txt", in.mem=FALSE, is.sym=FALSE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 8298)
expect_equal(sum(res), 103689)
file.remove("wiki-Vote.txt")

download.file("http://snap.stanford.edu/data/facebook_combined.txt.gz", "facebook.txt.gz")
system("gunzip facebook.txt.gz")
mat <- fm.load.sparse.matrix("facebook.txt", in.mem=TRUE, is.sym=TRUE, delim=" ")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 4039)
expect_equal(sum(res), 176468)

mat <- fm.load.sparse.matrix("facebook.txt", in.mem=FALSE, is.sym=TRUE, delim=" ")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 4039)
expect_equal(sum(res), 176468)
file.remove("facebook.txt")

download.file("http://snap.stanford.edu/data/soc-LiveJournal1.txt.gz",
"soc-LiveJournal1.txt.gz")
system("gunzip soc-LiveJournal1.txt.gz")
mat <- fm.load.sparse.matrix("soc-LiveJournal1.txt", in.mem=TRUE, is.sym=FALSE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 4847571)
expect_equal(sum(res), 68475391)

mat <- fm.load.sparse.matrix("soc-LiveJournal1.txt", in.mem=FALSE, is.sym=FALSE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(length(res), 4847571)
expect_equal(sum(res), 68475391)
file.remove("soc-LiveJournal1.txt")

download.file("http://snap.stanford.edu/data/bigdata/communities/com-lj.ungraph.txt.gz",
"com-lj.ungraph.txt.gz")
system("gunzip com-lj.ungraph.txt.gz")
mat <- fm.load.sparse.matrix("com-lj.ungraph.txt", in.mem=TRUE, is.sym=TRUE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(sum(res != 0), 3997962)
expect_equal(sum(res), 34681189 * 2)

mat <- fm.load.sparse.matrix("com-lj.ungraph.txt", in.mem=FALSE, is.sym=TRUE, delim="\t")
one <- fm.rep.int(1, nrow(mat))
res <- mat %*% one
expect_equal(sum(res != 0), 3997962)
expect_equal(sum(res), 34681189 * 2)
file.remove("facebook.txt")
})

for (type in type.set) {
test_that(paste("create a vector/matrix with repeat values of", type), {
if (type == "double") {
Expand Down
18 changes: 18 additions & 0 deletions inst/tests/test_dense.R
Original file line number Diff line number Diff line change
Expand Up @@ -1258,3 +1258,21 @@ test_that("test crossprod", {
expect_equal(typeof(fm.res), typeof(res))
expect_equal(fm.conv.FM2R(fm.res), res)
})

for (type in type.set) {
test_that("which.max", {
fm.mat <- get.mat(type, nrow=100, ncol=10)
agg.which.max <- fm.create.agg.op(fm.bo.which.max, NULL, "which.max")
res1 <- fm.conv.FM2R(fm.agg.mat(fm.mat, 1, agg.which.max))
res2 <- apply(fm.conv.FM2R(fm.mat), 1, function(x) which.max(x))
expect_equal(res1, res2)
})

test_that("which.min", {
fm.mat <- get.mat(type, nrow=100, ncol=10)
agg.which.min <- fm.create.agg.op(fm.bo.which.min, NULL, "which.min")
res1 <- fm.conv.FM2R(fm.agg.mat(fm.mat, 1, agg.which.min))
res2 <- apply(fm.conv.FM2R(fm.mat), 1, function(x) which.min(x))
expect_equal(res1, res2)
})
}
7 changes: 6 additions & 1 deletion src/matrix_interface.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -497,7 +497,12 @@ RcppExport SEXP R_FM_load_spm(SEXP pfile, SEXP pin_mem, SEXP pis_sym,
else if (ele_type == "D")
parsers.push_back(ele_parser::const_ptr(new int_parser<double>()));
std::vector<std::string> files(1, file);
data_frame::ptr df = read_data_frame(files, in_mem, delim, parsers);
dup_policy policy = dup_policy::NONE;
if (is_sym)
policy = dup_policy::REVERSE;
data_frame::ptr df = read_data_frame(files, in_mem, delim, parsers, policy);
if (df == NULL)
return R_NilValue;

sparse_matrix::ptr spm = create_2d_matrix(df,
block_2d_size(16 * 1024, 16 * 1024), type_p, is_sym, mat_name);
Expand Down

0 comments on commit 0e61857

Please sign in to comment.