Skip to content

Commit

Permalink
Adding package and function names to query plans
Browse files Browse the repository at this point in the history
  • Loading branch information
programLyrique committed Mar 28, 2023
1 parent 3f3c65b commit f29f647
Show file tree
Hide file tree
Showing 8 changed files with 131 additions and 6 deletions.
2 changes: 2 additions & 0 deletions R/sxpdb.R
Original file line number Diff line number Diff line change
Expand Up @@ -539,6 +539,8 @@ query_from_value <- function(value) {
#' * na: boolean
#' * ndims: integer
#' * attributes: boolean
#' * package: character vector of package names
#' * func: character vector of function names
#' @returns query object
#' @seealso [query_from_value()], [relax_query()], [close_query()], [view_db()], [map_db()]
#' @export
Expand Down
4 changes: 4 additions & 0 deletions src/classnames.h
Original file line number Diff line number Diff line change
Expand Up @@ -137,6 +137,10 @@ class ClassNames {
class_names.load_all();
}

bool is_loaded() const {
return class_names.is_loaded();
}

SEXP class_name_cache() const { return class_names.to_sexp();}

std::optional<uint32_t> get_class_id(const std::string& class_name) const {
Expand Down
12 changes: 10 additions & 2 deletions src/database.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -513,8 +513,16 @@ const std::optional<uint64_t> Database::sample_index() {

void Database::update_query(Query& query) const {
if(new_elements || !query.is_initialized()) {
// Make sure the reverse indexes are loaded.
const_cast<ClassNames&>(classes).load_all();
// Make sure the reverse indexes are loaded if we need classes
if(query.class_names.size() > 0) {
const_cast<ClassNames&>(classes).load_all();
}
// Make sure the origins are loaded
if(query.functions.size() > 0 || query.packages.size() > 0)
{
const_cast<Origins&>(origins).load_hashtables();
}

query.update(*this);
}
}
Expand Down
8 changes: 6 additions & 2 deletions src/origins.h
Original file line number Diff line number Diff line change
Expand Up @@ -194,11 +194,11 @@ class Origins {
const std::string& function_name(uint32_t i) const { return function_names.read(i);}
const std::string& param_name(uint32_t i) const { return param_names.read(i); }

const std::optional<uint64_t> package_id(const std::string& package_name) {
const std::optional<uint64_t> package_id(const std::string& package_name) const {
return package_names.get_index(package_name);
}

const std::optional<uint64_t> function_id(const std::string& function_name) {
const std::optional<uint64_t> function_id(const std::string& function_name) const {
return function_names.get_index(function_name);
}

Expand Down Expand Up @@ -266,6 +266,10 @@ class Origins {
// not for the parameters
}

bool is_loaded() const {
return package_names.is_loaded() && function_names.is_loaded();
}

uint64_t nb_values() const {
if(write_mode) {
return locations.size();
Expand Down
38 changes: 37 additions & 1 deletion src/query.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,7 @@ void Query::update(const Database& db) {
}
}

assert(class_names.size() == 0 || db.classes.is_loaded());
for(const std::string& class_name : class_names) {
std::optional<uint32_t> class_id = db.classes.get_class_id(class_name);

Expand All @@ -121,5 +122,40 @@ void Query::update(const Database& db) {
}
}
}
//index_cache.runOptimize(); // Maybe not worth it...

// refine with function and package name indexes
assert((packages.size() == 0 && functions.size() == 0) || db.origins.is_loaded());


for(const std::string& package_name : packages) {
auto pkg_id = db.origins.package_id(package_name);

if(pkg_id.has_value()) {
auto pkg_index = search_index.packages_index.at(pkg_id.value());
index_cache &= pkg_index;
}
}

for(const std::string& function_name : functions) {
auto fun_id = db.origins.function_id(function_name);

if(fun_id.has_value()) {
int bin_index = -1;
for(int i = 0 ; i < search_index.function_index.size() ; i ++) {
if(search_index.function_index[i].first > fun_id.value()) {
bin_index = i;
break;
}
}
if(bin_index == -1) {
bin_index = search_index.function_index.size() - 1;
}

if(bin_index >= 0) { // function index not empty
auto fun_index = search_index.search_function(db, search_index.function_index[bin_index].second, fun_id.value());
index_cache &= fun_index;
}
}
}

}
20 changes: 20 additions & 0 deletions src/query.h
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,8 @@ class Query {
std::optional<uint64_t> length;
std::optional<int> ndims; // 2 = matrix, 0 = nothing, otherwise = array
std::vector<std::string> class_names;
std::vector<std::string> packages;
std::vector<std::string> functions;
std::vector<Query> queries;// For union types, lists...
public:
Query(bool quiet_ = true) : quiet(quiet_), dist_cache(0, 0) {}
Expand Down Expand Up @@ -191,6 +193,22 @@ class Query {
else if (cur_name == "attributes") {
d.has_attributes = Rf_asLogical(cur_sexp);
}
else if (cur_name == "package") {
if(TYPEOF(cur_sexp) == STRSXP) {
d.packages = std::vector<std::string>(Rf_xlength(cur_sexp));
for(R_xlen_t j = 0; j < Rf_xlength(cur_sexp); j++) {
d.packages[j] = CHAR(STRING_ELT(cur_sexp, j));
}
}
}
else if (cur_name == "func") {
if(TYPEOF(cur_sexp) == STRSXP) {
d.functions = std::vector<std::string>(Rf_xlength(cur_sexp));
for(R_xlen_t j = 0; j < Rf_xlength(cur_sexp); j++) {
d.functions[j] = CHAR(STRING_ELT(cur_sexp, j));
}
}
}
}

return d;
Expand Down Expand Up @@ -237,6 +255,8 @@ class Query {
// Non quietness wins!
d.quiet = d1.quiet || d2.quiet;

// TODO: implement other query parameters


return d;
}
Expand Down
4 changes: 4 additions & 0 deletions src/table.h
Original file line number Diff line number Diff line change
Expand Up @@ -655,6 +655,10 @@ class UniqTextTable : public Table<std::string> {
unique_loaded = true;
}

bool is_loaded() const {
return unique_loaded;
}

uint64_t append_index(const std::string& value) {
auto it = unique_lines.find(value);

Expand Down
49 changes: 48 additions & 1 deletion tests/testthat/test-query.R
Original file line number Diff line number Diff line change
Expand Up @@ -208,7 +208,7 @@ test_that("dimensions", {
})


test_that("origin queries", {
test_that("origin queries with values_from_origin", {
l <- list(1L, "tu", 45.9, TRUE, c(2.1, 4))
origs <- rep.int(list(c("p", "fun", "param")), length(l))

Expand Down Expand Up @@ -249,3 +249,50 @@ test_that("origin queries", {

close(db)
})


test_that("origin queries with query plan ", {
l <- list(1L, "tu", 45.9, TRUE, c(2.1, 4))
origs <- rep.int(list(c("p", "fun", "param")), length(l))

# "tu"
origs[[2]][[1]] <- "package"

# TRUE
origs[[4]][[2]] <- "g"

# c(2.1, 4)
origs[[5]][[1]] <- "pack"
origs[[5]][[2]] <- "h"

has_search_index(db)

db <- db_from_values(l, origins = origs, with_search_index = TRUE)

expect_equal(nb_values_db(db), length(l))

q <- query_from_plan(list(package = "p"))
vals <- view_db(db, q)
expect_equal(length(vals), length(l) - 2)

q <- query_from_plan(list(package = "p", func = "fun"))
vals <- view_db(db, q)
expect_equal(length(vals), length(l) - 3)

q <- query_from_plan(list(package = "package", func = "fun"))
vals <- view_db(db, q)
expect_equal(length(vals), 1)
expect_equal(vals[[1]], "tu")

q <- query_from_plan(list(package = "p", func = "g"))
vals <- view_db(db, q)
expect_equal(length(vals), 1)
expect_equal(vals[[1]], TRUE)

q <- query_from_plan(list(package = "pack", func = "h"))
vals <- view_db(db, q)
expect_equal(length(vals), 1)
expect_equal(vals[[1]], c(2.1, 4))

close(db)
})

0 comments on commit f29f647

Please sign in to comment.